DBA Data[Home] [Help]

PACKAGE BODY: APPS.JTF_AM_FILTER_RESOURCE_PVT

Source


1 PACKAGE BODY JTF_AM_FILTER_RESOURCE_PVT AS
2 /* $Header: jtfamvsb.pls 120.2 2006/04/06 02:18:35 sbarat ship $ */
3 
4 PROCEDURE SEARCH_SKILL
5     (   p_api_version                         IN  NUMBER,
6         p_init_msg_list                       IN  VARCHAR2 ,
7         p_commit                              IN  VARCHAR2 ,
8         x_assign_resources_tbl                IN  OUT NOCOPY JTF_ASSIGN_PUB.AssignResources_tbl_type,
9         p_skill_param_tbl                     IN  JTF_AM_FILTER_RESOURCE_PVT.skill_param_tbl_type,
10         x_return_status                       OUT NOCOPY VARCHAR2,
11         x_msg_count                           OUT NOCOPY NUMBER,
12         x_msg_data                            OUT NOCOPY VARCHAR2)
13 
14 IS
15 
16   l_assign_resource_tbl           JTF_ASSIGN_PUB.AssignResources_tbl_type;
17 
18   cursor c_rule(l_document_type  in varchar2,
19                 l_product_id_passed     in number,
20                 l_category_id_passed    in number,
21                 l_problem_code_passed   in number,
22                 l_component_id_passed   in number)
23       is
24   SELECT r1.rule_id
25          , r1.product_id_passed
26          , r1.category_id_passed
27          , r1.problem_code_passed
28          , r1.component_id_passed
29     FROM jtf_am_skill_rules r1
30    WHERE r1.document_type = l_document_type
31      AND r1.product_id_passed    = l_product_id_passed
32      AND r1.category_id_passed   = l_category_id_passed
33      AND r1.problem_code_passed = l_problem_code_passed
34      AND r1.component_id_passed = l_component_id_passed
35      AND r1.active_flag = 'Y';
36 
37  r_rule    c_rule%rowtype;
38 
39   cursor c_rule_dtl(l_rule_id in number)
40       is
41   SELECT sk.detail_id
42          , sk.check_product_id
43          , sk.check_problem_code
44          , sk.check_category_id
45          , sk.check_component_id
46     FROM jtf_am_skill_rule_dtls  sk
47    WHERE sk.rule_id = l_rule_id
48      AND sk.active_flag = 'Y'
49    ORDER BY rank;
50 
51   r_rule_dtl   c_rule_dtl%rowtype;
52 
53  l_api_version           NUMBER := 1.0;
54  l_api_name              varchar2(30) := 'SEARCH_SKILL';
55  l_product_id_passed     number := 0;
56  l_category_id_passed    number := 0;
57  l_problem_code_passed   number := 0;
58  l_component_id_passed   number := 0;
59 
60  l_stmt_more            varchar2(4000) := null;
61  l_stmt                 varchar2(4000) := null;
62  l_stmt_add             varchar2(4000) := null;
63 
64  TYPE DYNAMIC_CUR_TYP   IS REF CURSOR;
65  c_res_skills           DYNAMIC_CUR_TYP;
66 
67  l_current_record       number  := 0;
68  l_count                number  := 0;
69  i                      number  := 0;
70  l_skill_level          number  := 0;
71  l_skill_name           VARCHAR2(2000);
72  l_rule_dtl_found       varchar2(1) := 0;
73 
74  -- variables for dynamic bind to query
75  TYPE bind_rec_type IS record (bind_value varchar2(2000));
76  TYPE  bind_tbl_type IS table OF bind_rec_type INDEX BY binary_integer;
77  l_bind_counter         number := 0;
78  bind_table             bind_tbl_type;
79 
80 BEGIN
81    x_return_status := fnd_api.g_ret_sts_success;
82 
83    --Standard Call to check  API compatibility
84    IF NOT FND_API.Compatible_API_CALL(l_API_VERSION,P_API_VERSION,L_API_NAME,G_PKG_NAME)
85    THEN
86       RAISE FND_API.G_EXC_ERROR;
87    END IF;
88 
89     --Initialize the message List   if P_INIT_MSG_LIST is set to TRUE
90     IF FND_API.To_boolean(P_INIT_MSG_LIST)
91     THEN
92         FND_MSG_PUB.Initialize;
93     END IF;
94    -- create statement
95    l_stmt_more := 'SELECT  s.skill_level , s.level_name '||
96                    ' FROM  jtf_rs_resource_skills r, jtf_rs_skill_levels_vl s ' ||
97                   ' WHERE  r.skill_level_id = s.skill_level_id '||
98                    '  AND  r.resource_id   = :x_resource_id ';
99 
100    -- find values passed in from calling document
101    if(p_skill_param_tbl(1).product_id is not null and p_skill_param_tbl(1).product_org_id is not null)
102    then
103       l_product_id_passed := 1;
104    else
105       l_product_id_passed := 0;
106    end if;
107    if(p_skill_param_tbl(1).category_id is not null)
108    then
109       l_category_id_passed := 1;
110    else
111       l_category_id_passed := 0;
112    end if;
113    if(p_skill_param_tbl(1).problem_code is not null)
114    then
115       l_problem_code_passed := 1;
116    else
117       l_problem_code_passed := 0;
118    end if;
119    if(p_skill_param_tbl(1).component_id is not null)
120    then
121       l_component_id_passed := 1;
122    else
123       l_component_id_passed := 0;
124    end if;
125 
126 -- get the rule id from the header table based on the values passed in
127   open c_rule(p_skill_param_tbl(1).document_type
128               , l_product_id_passed
129               , l_category_id_passed
130               , l_problem_code_passed
131               , l_component_id_passed);
132   fetch c_rule into r_rule;
133   if(c_rule%found)
134   then
135     open c_rule_dtl(r_rule.rule_id);
136     fetch c_rule_dtl into r_rule_dtl;
137     while(c_rule_dtl%found)
138     loop
139 
140        l_stmt := null;
141        i := 0;
142        l_bind_counter := 0;
143         bind_table.delete;
144 
145        -- check if product should be considered and add to dynamic sql
146        if(r_rule_dtl.check_product_id = 1)
147        then
148          l_stmt := l_stmt ||' AND  product_id = :x_product_id and product_org_id = :x_product_org_id';
149          i      := l_bind_counter + 1;
150          bind_table(i).bind_value :=  p_skill_param_tbl(1).product_id;
151          i := i +1;
152          bind_table(i).bind_value :=  p_skill_param_tbl(1).product_org_id;
153          l_bind_counter := i;
154        else
155          l_stmt := l_stmt ||' AND product_id is null';
156        end if;
157 
158        -- check if category should be considered and add to dynamic sql
159        if(r_rule_dtl.check_category_id = 1)
160        then
161          l_stmt := l_stmt ||' AND  category_id = :x_category_id ';
162          i      := l_bind_counter + 1;
163          bind_table(i).bind_value :=  p_skill_param_tbl(1).category_id;
164          l_bind_counter := i;
165        else
166          l_stmt := l_stmt ||' AND category_id is null';
167        end if;
168 
169 
170        -- check if problem should be considered and add to dynamic sql
171        if(r_rule_dtl.check_problem_code = 1)
172        then
173          l_stmt := l_stmt ||' AND  problem_code = :x_problem_code ';
174          i      := l_bind_counter + 1;
175          bind_table(i).bind_value :=  p_skill_param_tbl(1).problem_code;
176          l_bind_counter := i;
177        else
178          l_stmt := l_stmt ||' AND problem_code is null';
179        end if;
180 
181        -- check if component id should be considered and add to dynamic sql
182        if(r_rule_dtl.check_component_id = 1)
183        then
184          l_stmt := l_stmt ||' AND  component_id = :x_component_id ';
185          i      := l_bind_counter + 1;
186          bind_table(i).bind_value :=  p_skill_param_tbl(1).component_id;
187          l_bind_counter := i;
188        else
189          l_stmt := l_stmt ||' AND component_id is null';
190        end if;
191 
192        --if(l_stmt is not null)
193        if(l_bind_counter > 0 )
194        then
195 
196         -- mark the rule dtl found flag if at least one rule found
197            l_rule_dtl_found := 1;
198 
199         -- Query for skills if there is atleast one record in the in table
200         IF ( x_assign_resources_tbl.COUNT > 0 ) THEN
201 
202         l_current_record := x_assign_resources_tbl.FIRST;
203 
204         WHILE l_current_record <= x_assign_resources_tbl.LAST
205         LOOP
206             if( x_assign_resources_tbl(l_current_record).resource_type not in ('RS_GROUP', 'RS_TEAM')
207                                               -- Modified by SBARAT on 06/04/2006 for bug# 5104535
208                                               AND  x_assign_resources_tbl(l_current_record).skill_name is null) --skill_level is null)
209             then
210                -- execute query for the resource based on bind variables to use
211                if(l_bind_counter = 1)
212                then
213                     OPEN c_res_skills FOR l_stmt_more||l_stmt USING
214                                                   x_assign_resources_tbl(l_current_record).resource_id,
215                                                   bind_table(1).bind_value;
216                elsif(l_bind_counter = 2)
217                then
218                     OPEN c_res_skills FOR l_stmt_more||l_stmt USING
219                                                   x_assign_resources_tbl(l_current_record).resource_id,
220                                                   bind_table(1).bind_value,
221                                                   bind_table(2).bind_value;
222                elsif(l_bind_counter = 3)
223                then
224                     OPEN c_res_skills FOR l_stmt_more||l_stmt USING
225                                                   x_assign_resources_tbl(l_current_record).resource_id,
226                                                   bind_table(1).bind_value,
227                                                   bind_table(2).bind_value,
228                                                   bind_table(3).bind_value;
229                elsif(l_bind_counter = 4)
230                then
231                     OPEN c_res_skills FOR l_stmt_more||l_stmt USING
232                                                   x_assign_resources_tbl(l_current_record).resource_id,
233                                                   bind_table(1).bind_value,
234                                                   bind_table(2).bind_value,
235                                                   bind_table(3).bind_value,
236                                                   bind_table(4).bind_value;
237                elsif(l_bind_counter = 5)
238                then
239                     OPEN c_res_skills FOR l_stmt_more||l_stmt USING
240                                                   x_assign_resources_tbl(l_current_record).resource_id,
241                                                   bind_table(1).bind_value,
242                                                   bind_table(2).bind_value,
243                                                   bind_table(3).bind_value,
244                                                   bind_table(4).bind_value,
245                                                   bind_table(5).bind_value;
246                elsif(l_bind_counter = 6)
247                then
248                     OPEN c_res_skills FOR l_stmt_more||l_stmt USING
249                                                   x_assign_resources_tbl(l_current_record).resource_id,
250                                                   bind_table(1).bind_value,
251                                                   bind_table(2).bind_value,
252                                                   bind_table(3).bind_value,
253                                                   bind_table(4).bind_value,
254                                                   bind_table(5).bind_value,
255                                                   bind_table(6).bind_value;
256                end if;
257 
258 
259 
260                FETCH  c_res_skills INTO l_skill_level, l_skill_name;
261                IF(c_res_skills%FOUND)
262                THEN
263                   -- check if skill level is greater than 0
264                    IF ( l_skill_level > 0 ) THEN
265                         x_assign_resources_tbl(l_current_record).skill_level  := l_skill_level;
266                         x_assign_resources_tbl(l_current_record).skill_name   := l_skill_name;
267                    ELSE
268                         x_assign_resources_tbl(l_current_record).skill_level  := 0;
269                         x_assign_resources_tbl(l_current_record).skill_name   := null;
270                    END IF; -- End of l_skill_level > 0
271                ELSE
272                         x_assign_resources_tbl(l_current_record).skill_level  := 0;
273                         x_assign_resources_tbl(l_current_record).skill_name   := null;
274                END IF;
275                close c_res_skills;
276            end if;
277           l_current_record := x_assign_resources_tbl.NEXT(l_current_record);
278         END LOOP; -- end of x_assign_resource_tables
279        END IF; --End of x_assign_resources_tbl.COUNT > 0
280        end if; -- end of if condition for bind variable
281       fetch c_rule_dtl into r_rule_dtl;
282     end loop; -- end of c_rule_dtl found
283     close c_rule_dtl;
284 
285 
286     -- if at least one rule dtl is found then filter out resources that do not have required skills
287     -- this filtering is not to be done anymore. the skills are indicated in the skill levels. its upto
288     -- the calling document to filter resources using their own logic. this is because of the bug 2905237.
289     -- Filtering for skills is not to be done as mentioned in the bug
290 /*
291      IF(l_rule_dtl_found = 1)
292      THEN
293         i :=  x_assign_resources_tbl.FIRST;
294         WHILE(i <=  x_assign_resources_tbl.LAST)
295         LOOP
296         IF (x_assign_resources_tbl(i).resource_type not in ('RS_TEAM', 'RS_GROUP')) THEN
297            IF (nvl(x_assign_resources_tbl(i).skill_level,0) > 0 ) THEN
298              l_count := l_count + 1;
299              l_assign_resource_tbl(l_count).resource_id           := x_assign_resources_tbl(i).resource_id;
300              l_assign_resource_tbl(l_count).resource_type         := x_assign_resources_tbl(i).resource_type;
301              l_assign_resource_tbl(l_count).terr_rsc_id           := x_assign_resources_tbl(i).terr_rsc_id;
302              l_assign_resource_tbl(l_count).role                  := x_assign_resources_tbl(i).role ;
303              l_assign_resource_tbl(l_count).start_date            := x_assign_resources_tbl(i).start_date;
304              l_assign_resource_tbl(l_count).end_date              := x_assign_resources_tbl(i).end_date;
305              l_assign_resource_tbl(l_count).shift_construct_id    := x_assign_resources_tbl(i).shift_construct_id;
306              l_assign_resource_tbl(l_count).terr_id               := x_assign_resources_tbl(i).terr_id ;
307              l_assign_resource_tbl(l_count).terr_name             := x_assign_resources_tbl(i).terr_name;
308              l_assign_resource_tbl(l_count).primary_contact_flag  := x_assign_resources_tbl(i).primary_contact_flag;
309              l_assign_resource_tbl(l_count).primary_flag          := x_assign_resources_tbl(i).primary_flag;
310              l_assign_resource_tbl(l_count).terr_rank             := x_assign_resources_tbl(i).terr_rank;
311              l_assign_resource_tbl(l_count).travel_time           := x_assign_resources_tbl(i).travel_time;
312              l_assign_resource_tbl(l_count).travel_uom            := x_assign_resources_tbl(i).travel_uom;
313              l_assign_resource_tbl(l_count).preference_type       := x_assign_resources_tbl(i).preference_type;
314              l_assign_resource_tbl(l_count).full_access_flag      := x_assign_resources_tbl(i).full_access_flag;
315              l_assign_resource_tbl(l_count).group_id              := x_assign_resources_tbl(i).group_id;
316              l_assign_resource_tbl(l_count).location              := x_assign_resources_tbl(i).location;
317              l_assign_resource_tbl(l_count).trans_object_id       := x_assign_resources_tbl(i).trans_object_id;
318              l_assign_resource_tbl(l_count).support_site_id       := x_assign_resources_tbl(i).support_site_id;
319              l_assign_resource_tbl(l_count).support_site_name     := x_assign_resources_tbl(i).support_site_name;
320              l_assign_resource_tbl(l_count).web_availability_flag := x_assign_resources_tbl(i).web_availability_flag;
321              l_assign_resource_tbl(l_count).skill_level           := x_assign_resources_tbl(i).skill_level;
322              l_assign_resource_tbl(l_count).skill_name            := x_assign_resources_tbl(i).skill_name;
323            END IF;
324 
325          ELSE
326              l_count := l_count + 1;
327              l_assign_resource_tbl(l_count).resource_id           := x_assign_resources_tbl(i).resource_id;
331              l_assign_resource_tbl(l_count).start_date            := x_assign_resources_tbl(i).start_date;
328              l_assign_resource_tbl(l_count).resource_type         := x_assign_resources_tbl(i).resource_type;
329              l_assign_resource_tbl(l_count).terr_rsc_id           := x_assign_resources_tbl(i).terr_rsc_id;
330              l_assign_resource_tbl(l_count).role                  := x_assign_resources_tbl(i).role ;
332              l_assign_resource_tbl(l_count).end_date              := x_assign_resources_tbl(i).end_date;
333              l_assign_resource_tbl(l_count).shift_construct_id    := x_assign_resources_tbl(i).shift_construct_id;
334              l_assign_resource_tbl(l_count).end_date              := x_assign_resources_tbl(i).end_date;
335              l_assign_resource_tbl(l_count).shift_construct_id    := x_assign_resources_tbl(i).shift_construct_id;
336              l_assign_resource_tbl(l_count).terr_id               := x_assign_resources_tbl(i).terr_id ;
337              l_assign_resource_tbl(l_count).terr_name             := x_assign_resources_tbl(i).terr_name;
338              l_assign_resource_tbl(l_count).primary_contact_flag  := x_assign_resources_tbl(i).primary_contact_flag;
339              l_assign_resource_tbl(l_count).primary_flag          := x_assign_resources_tbl(i).primary_flag;
340              l_assign_resource_tbl(l_count).terr_rank             := x_assign_resources_tbl(i).terr_rank;
341              l_assign_resource_tbl(l_count).travel_time           := x_assign_resources_tbl(i).travel_time;
342              l_assign_resource_tbl(l_count).travel_uom            := x_assign_resources_tbl(i).travel_uom;
343              l_assign_resource_tbl(l_count).preference_type       := x_assign_resources_tbl(i).preference_type;
344              l_assign_resource_tbl(l_count).full_access_flag      := x_assign_resources_tbl(i).full_access_flag;
345              l_assign_resource_tbl(l_count).group_id              := x_assign_resources_tbl(i).group_id;
346              l_assign_resource_tbl(l_count).location              := x_assign_resources_tbl(i).location;
347              l_assign_resource_tbl(l_count).trans_object_id       := x_assign_resources_tbl(i).trans_object_id;
348              l_assign_resource_tbl(l_count).support_site_id       := x_assign_resources_tbl(i).support_site_id;
349              l_assign_resource_tbl(l_count).support_site_name     := x_assign_resources_tbl(i).support_site_name;
350              l_assign_resource_tbl(l_count).web_availability_flag := x_assign_resources_tbl(i).web_availability_flag;
351              l_assign_resource_tbl(l_count).skill_level           := x_assign_resources_tbl(i).skill_level;
352              l_assign_resource_tbl(l_count).skill_name            := x_assign_resources_tbl(i).skill_name;
353          END IF;
354          i := i + 1;
355        END LOOP;
356        x_assign_resources_tbl.delete;
357        x_assign_resources_tbl := l_assign_resource_tbl;
358 
359        END IF; -- end of if rule dtl found
360 */
361   end if; -- end if c_rule found
362 
363   close c_rule;
364 
365     FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
366 
367   EXCEPTION
368    WHEN fnd_api.g_exc_unexpected_error
369    THEN
370       FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
371    WHEN fnd_api.g_exc_error
372    THEN
373       FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
374    WHEN OTHERS
375    THEN
376       fnd_message.set_name ('JTF', 'JTF_AM_UNEXP_ERROR');
377       fnd_message.set_token('P_SQLCODE',SQLCODE);
378       fnd_message.set_token('P_SQLERRM',SQLERRM);
379       fnd_message.set_token('P_API_NAME',l_api_name);
380       FND_MSG_PUB.add;
381       x_return_status := fnd_api.g_ret_sts_unexp_error;
382       FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
383 
384 END SEARCH_SKILL;
385 
386 -- this is called JTF_ASSIGN_PUB.get_assign_sr_resources
387  PROCEDURE SERVICE_SECURITY_CHECK
388     (   p_api_version                         IN  NUMBER,
389         p_init_msg_list                       IN  VARCHAR2 ,
390         p_commit                              IN  VARCHAR2 ,
391         x_assign_resources_tbl                IN  OUT NOCOPY JTF_ASSIGN_PUB.AssignResources_tbl_type,
392         p_sr_tbl                              IN  JTF_AM_FILTER_RESOURCE_PVT.sr_rec_type,
393         x_return_status                       OUT NOCOPY VARCHAR2,
394         x_msg_count                           OUT NOCOPY NUMBER,
395         x_msg_data                            OUT NOCOPY VARCHAR2)
396 IS
397 
398  l_api_version           NUMBER := 1.0;
399  l_api_name              varchar2(30) := 'SERVICE_SECURITY_CHECK';
400  l_resource_tbl          JTF_AM_FILTER_RESOURCE_PVT.resource_tbl_type;
401  l_assign_resources_tbl  JTF_ASSIGN_PUB.AssignResources_tbl_type;
402  l_msg_count             NUMBER;
403  l_msg_data              VARCHAR2(2000);
404  l_return_status         VARCHAR2(10);
405  l_resource_id           JTF_NUMBER_TABLE           := JTF_NUMBER_TABLE();
406  l_resource_type         JTF_VARCHAR2_TABLE_100     := JTF_VARCHAR2_TABLE_100();
407  l_count                 number := 0;
408  i                       number := 0;
409  l_current_rec           number := 0;
410  l_temp                  number := 0;
411 BEGIN
412    x_return_status := fnd_api.g_ret_sts_success;
413    --Standard Call to check  API compatibility
414    IF NOT FND_API.Compatible_API_CALL(l_API_VERSION,P_API_VERSION,L_API_NAME,G_PKG_NAME)
415    THEN
416       RAISE FND_API.G_EXC_ERROR;
417    END IF;
418 
419     --Initialize the message List   if P_INIT_MSG_LIST is set to TRUE
420     IF FND_API.To_boolean(P_INIT_MSG_LIST)
421     THEN
422         FND_MSG_PUB.Initialize;
423     END IF;
424 
425    IF(x_assign_resources_tbl.count > 0)
426    THEN
427      l_resource_id.extend(x_assign_resources_tbl.count);
428      l_resource_type.extend(x_assign_resources_tbl.count);
429    END IF;
430 
431    -- assign the values of the in table to local variables that will be used as bind variable
432    IF(x_assign_resources_tbl.count > 0)
433    THEN
434 
435     l_count := x_assign_resources_tbl.first;
436     i := 1;
437     while(l_count <= x_assign_resources_tbl.last)
438     loop
439 
440        l_resource_id(i)   := x_assign_resources_tbl(l_count).resource_id;
441        l_resource_type(i) := x_assign_resources_tbl(l_count).resource_type;
442        l_count := l_count + 1;
443        i := i+1;
444     end loop; -- check for l_count
445 
446       -- processing logic for security check
447       EXECUTE IMMEDIATE
448       '
449       DECLARE
450 
451         l_sr_rec                       CS_SR_SECURITY_GRP.sr_rec_type;
452         l_resource_id                  JTF_NUMBER_TABLE           := JTF_NUMBER_TABLE();
453         l_resource_type                JTF_VARCHAR2_TABLE_100     := JTF_VARCHAR2_TABLE_100();
454         l_return_status                VARCHAR2(10);
455         l_msg_count                    NUMBER;
456         l_msg_data                     VARCHAR2(2000);
457         l_sr_resource_tbl              CS_SR_SECURITY_GRP.RESOURCE_VALIDATE_TBL_TYPE := CS_SR_SECURITY_GRP.RESOURCE_VALIDATE_TBL_TYPE();
458 
459         i        BINARY_INTEGER;
460         l_indx   BINARY_INTEGER;
461 
462       BEGIN
463 
464         l_resource_id.extend(1000);
465         l_resource_type.extend(1000);
466         l_sr_rec.incident_id      := :1;
467         l_sr_rec.incident_type_id := :2;
468         l_resource_id             := :3;
469         l_resource_type           := :4;
470          --assign values to l_sr_resource_tbl
471         l_indx := l_resource_id.first;
472         i := 1;
473         While(l_indx <= l_resource_id.last)
474         LOOP
475            l_sr_resource_tbl.extend();
476            l_sr_resource_tbl(l_indx).resource_id   := l_resource_id(l_indx);
477            l_sr_resource_tbl(l_indx).resource_type := l_resource_type(l_indx);
478            i := 1 + 1;
479            l_indx := l_indx + 1;
480         END LOOP;
481          -- call sr security api
482         CS_SR_SECURITY_GRP.validate_resource
483         (
484            p_api_version          => :5
485            ,p_init_msg_list       => :6
486            ,p_commit              => FND_API.g_false
487            ,p_sr_rec              => l_sr_rec
488            ,px_resource_tbl       => l_sr_resource_tbl
489            ,x_return_status       => l_return_status
490            ,x_msg_count           => l_msg_count
491            ,x_msg_data             => l_msg_data
492         );
493 
494         :7 := l_msg_count;
495         :8 := l_msg_data;
496         :9 := l_return_status;
497 
498         IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
499           -- Unexpected Execution Error from call to Contracts API
500           fnd_message.set_name('||''''||'JTF'||''''||','||''''||'JTF_AM_ERROR_SERVICE_API'||''''||');'||
501          'fnd_msg_pub.add;
502             IF (l_return_status = fnd_api.g_ret_sts_error) THEN
503               RAISE fnd_api.g_exc_error;
504             ELSE
505               RAISE fnd_api.g_exc_unexpected_error;
506             END IF;
507         END IF;
508 
509         --assign values to out tables
510         l_indx := l_sr_resource_tbl.first;
511         l_resource_id.delete;
512         l_resource_type.delete;
513         l_resource_id     := JTF_NUMBER_TABLE();
514         l_resource_type   := JTF_VARCHAR2_TABLE_100();
515 
516         IF(l_sr_resource_tbl.count > 0)
517         THEN
518            l_resource_id.extend(l_sr_resource_tbl.count);
519            l_resource_type.extend(l_sr_resource_tbl.count);
520            i := 1;
521            While(l_indx <= l_sr_resource_tbl.last)
522            LOOP
523               l_resource_id(i)   := l_sr_resource_tbl(l_indx).resource_id;
524               l_resource_type(i) := l_sr_resource_tbl(l_indx).resource_type;
525               l_indx := l_indx + 1;
526               i := i + 1;
527             END LOOP;
528           END IF; -- end of check table count
529 
530          -- added these two lines to fix bug 3560402
531          -- the in/out parameters do not work. instead using out parameters specifically
532          :10 := l_resource_id;
533          :11 := l_resource_type;
534 
535       END;
536       '
537       USING IN  p_sr_tbl.incident_id,
538             IN  p_sr_tbl.incident_type_id,
539             IN  OUT l_resource_id,
540             IN  OUT l_resource_type,
541             IN  p_api_version,
542             IN  p_init_msg_list,
543             OUT l_msg_count,
544             OUT l_msg_data,
545             OUT l_return_status,
546          -- added these two lines to fix bug 3560402
547          -- the in/out parameters do not work. instead using out parameters specifically
548             OUT l_resource_id,
549             OUT l_resource_type;
550 
551       x_return_status  := l_return_status;
552       x_msg_count      := l_msg_count;
553       x_msg_data       := l_msg_data;
554 
555 
556  -- assign values back to x_assign_resources_tbl
557       l_assign_resources_tbl := x_assign_resources_tbl;
558       x_assign_resources_tbl.delete;
559       l_count := l_assign_resources_tbl.first;
560       l_current_rec := 0;
561       while(l_count <= l_assign_resources_tbl.last)
562       Loop
563          l_temp := l_resource_id.first;
564          while(l_temp <= l_resource_id.last)
565          loop
566              If(l_resource_id(l_temp) = l_assign_resources_tbl(l_count).resource_id
567                  AND l_resource_type(l_temp) = l_assign_resources_tbl(l_count).resource_type)
568              THEN
569                     x_assign_resources_tbl(l_current_rec) := l_assign_resources_tbl(l_count);
570                     l_current_rec := l_current_rec + 1;
571                     exit;
572              END IF; -- end of resource id and type comparison
573              l_temp := l_temp + 1;
574           end loop; -- end of l_temp check
575           l_count := l_count + 1;
576      end loop; -- end of l_count check
577 
578  END IF; -- end of check for count in x_assign_resources_tbl
579 
580 
581 EXCEPTION
582    WHEN fnd_api.g_exc_unexpected_error
583    THEN
584       FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
585    WHEN fnd_api.g_exc_error
586    THEN
587       FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
588    WHEN OTHERS
589    THEN
590       fnd_message.set_name ('JTF', 'JTF_AM_UNEXP_ERROR');
591       fnd_message.set_token('P_SQLCODE',SQLCODE);
592       fnd_message.set_token('P_SQLERRM',SQLERRM);
593       fnd_message.set_token('P_API_NAME',l_api_name);
594       FND_MSG_PUB.add;
595       x_return_status := fnd_api.g_ret_sts_unexp_error;
596       FND_MSG_PUB.count_and_get (p_count => x_msg_count, p_data => x_msg_data);
597 
598 END SERVICE_SECURITY_CHECK;
599 
600 END JTF_AM_FILTER_RESOURCE_PVT;