DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_RESOURCE_UTILS

Source


1 PACKAGE BODY pa_resource_utils AS
2 -- $Header: PARSUTLB.pls 120.54.12020000.2 2012/10/31 07:19:49 svmohamm ship $
3 --
4 --  PROCEDURE
5 --              check_internal_or_external
6 --  PURPOSE
7 --              This procedure returns the correct resource_type_id
8 --              for a given resource name (whether Employee or Party).
9 --              Raise no_data_found or too_many_rows, if no resource
10 --              exists or more than one resource has the same name
11 --  HISTORY
12 --   26-APR-2002      Adzilah A.       Created
13 PROCEDURE check_internal_or_external(p_resource_name     IN   VARCHAR2,
14                                      x_resource_type_id  OUT  NOCOPY NUMBER, --File.Sql.39 bug 4440895
15                                      x_return_status     OUT  NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
16  IS
17 
18      CURSOR internal IS
19          SELECT 'Y'
20          FROM   per_all_people_f
21          WHERE  full_name = p_resource_name
22            and  rownum=1;
23 
24      CURSOR external IS
25          SELECT 'Y'
26      FROM   pa_party_resource_details_v
27          WHERE  party_name = p_resource_name
28            and  rownum=1;
29 
30      l_internal  VARCHAR2(1)  := 'N';
31      l_external  VARCHAR2(1)  := 'N';
32 
33 BEGIN
34 
35      OPEN internal;
36      FETCH internal into l_internal;
37      CLOSE internal;
38 
39      --dbms_output.put_line('INTERNAL = ' || l_internal);
40 
41      OPEN external;
42      FETCH external into l_external;
43      CLOSE external;
44 
45      --dbms_output.put_line('EXTERNAL = ' || l_external);
46 
47      if(l_internal = 'Y' and l_external = 'Y') then
48          raise TOO_MANY_ROWS;
49 
50      elsif (l_internal='Y' and l_external= 'N') then
51          -- EMPLOYEE
52          x_resource_type_id := 101;
53 
54      elsif (l_internal='N' and l_external= 'Y') then
55          -- HZ_PARTY
56          x_resource_type_id := 112;
57      else
58          raise NO_DATA_FOUND;
59      end if;
60 
61      x_return_status := FND_API.G_RET_STS_SUCCESS;
62 
63 EXCEPTION
64      WHEN NO_DATA_FOUND THEN
65      x_return_status := FND_API.G_RET_STS_ERROR;
66          raise;
67      WHEN TOO_MANY_ROWS THEN
68      x_return_status := FND_API.G_RET_STS_ERROR;
69      raise;
70      WHEN OTHERS THEN
71      x_return_status := FND_API.G_RET_STS_ERROR;
72      raise;
73 END check_internal_or_external;
74 
75 
76 --
77 --  PROCEDURE
78 --              Check_ResourceName_Or_Id
79 --  PURPOSE
80 --              This procedure does the following
81 --              If Resource name is passed converts it to the id
82 --      If Resource Id is passed,
83 --      based on the check_id_flag validates it
84 --  HISTORY
85 --   27-JUN-2000      P. Bandla       Created
86 --   19-JUL-2000      E  Yefimov      Modified
87 --     Added resource_type_id as an out parameter
88 --   05-SEP-2000      P. Bandla       Modified
89 --     Added p_date parameter
90 --   11-APR-2001      virangan        Added LOV fixes
91 
92  PROCEDURE Check_ResourceName_Or_Id(
93             p_resource_id       IN  NUMBER,
94             p_resource_name     IN  VARCHAR2,
95             p_date              IN  DATE,
96    	    p_end_date          IN  DATE :=null, -- 3235018
97             p_check_id_flag     IN  VARCHAR2,
98                         p_resource_type_id      IN      NUMBER,
99             x_resource_id       OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
100             x_resource_type_id      OUT     NOCOPY NUMBER, --File.Sql.39 bug 4440895
101             x_return_status     OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
102             x_error_message_code    OUT NOCOPY VARCHAR2 )  --File.Sql.39 bug 4440895
103   IS
104 
105           -- l_sys_per_type       VARCHAR2(30);
106           l_current_id         NUMBER     := NULL;
107           l_num_ids            NUMBER     := 0;
108           l_id_found_flag      VARCHAR(1) := 'N';
109           l_resource_type_id   NUMBER     := p_resource_type_id;
110 
111          /* Added for Bug# 6056112 */
112           l_pa_resource_id     NUMBER ;
113           l_future_term_wf_flag   pa_resources.future_term_wf_flag%TYPE := NULL  ;
114 
115           CURSOR r_ids IS
116               SELECT person_id
117               FROM   per_all_people_f
118               WHERE  full_name = p_resource_name
119           AND    trunc(p_date) between trunc(effective_start_date)
120                                        and trunc(effective_end_date);
121 
122  BEGIN
123 
124      IF (p_resource_id IS NULL and p_resource_name IS NOT NULL) THEN
125           check_internal_or_external (
126                p_resource_name      => p_resource_name,
127                x_resource_type_id   => l_resource_type_id,
128                x_return_status      => x_return_status);
129 
130      END IF;
131 
132     /* Start of Changes for Bug 6056112 */
133      SELECT  pa_resource_utils.get_resource_id(p_resource_id)
134      INTO l_pa_resource_id
135      FROM dual;
136 
137      IF (l_pa_resource_id <> -999) THEN
138              SELECT nvl(future_term_wf_flag,'N')
139             INTO l_future_term_wf_flag
140             FROM pa_resources
141             WHERE resource_id = l_pa_resource_id;
142      END IF ;
143     /* End of Changes for Bug 6056112 */
144 
145      --dbms_output.put_line('Resource Type Id = ' || l_resource_type_id);
146 
147      -----------------------------------------
148      -- This check is for EMPLOYEE type
149      -- because we now handle external people
150      -----------------------------------------
151      IF l_resource_type_id = 101 THEN
152 
153     IF p_resource_id IS NOT NULL AND p_resource_id<>FND_API.G_MISS_NUM THEN
154 
155         IF p_check_id_flag = 'Y' THEN
156 
157           /* Start of Changes for Bug 6056112 */
158           IF (nvl(l_future_term_wf_flag,'N') = 'Y') THEN
159 
160            SELECT  DISTINCT(prd.person_id)
161            INTO   x_resource_id
162            FROM pa_resources_denorm prd
163            WHERE prd.person_id = p_resource_id
164            AND  trunc(p_date) > = (Select trunc(min(prd1.resource_effective_start_date))
165                                    from pa_resources_denorm prd1
166                                    where prd1.person_id = prd.person_id)
167            AND (trunc(p_end_date) is null
168                        OR
169                 trunc(p_end_date) < = (Select trunc(max(prd2.resource_effective_end_date))
170                                        from pa_resources_denorm prd2
171                                        where prd2.person_id = prd.person_id) );
172           ELSE
173 
174             SELECT per.person_id
175                    -- type.system_person_type -- FP M CWK
176                 INTO   x_resource_id
177                    -- l_sys_per_type
178                 FROM   per_all_people_f per
179                                -- per_person_types type
180                 WHERE  per.person_id = p_resource_id
181                         -- AND    per.person_type_id = type.person_type_id
182             AND trunc(p_date) between trunc(per.effective_start_date) and trunc(per.effective_end_date)
183             AND (p_end_date is null
184                          OR
185                 -- Start changes for Bug 6828493
186                 --(trunc(p_end_date) between trunc(per.effective_start_date) and trunc(per.effective_end_date))
187                 (trunc(p_end_date) < =     (Select trunc(max(per2.effective_end_date))
188                                             from per_all_people_f per2
189                                             where per2.person_id = p_resource_id
190                                             AND (per2.current_employee_flag = 'Y' OR per2.current_npw_flag = 'Y')) -- AND Codn added for bug 6851095
191                  AND trunc(p_end_date) > = (Select trunc(min(per3.effective_start_date))
192                                             from per_all_people_f per3
193                                             where per3.person_id = p_resource_id
194                                             AND (per3.current_employee_flag = 'Y' OR per3.current_npw_flag = 'Y')))) -- AND Codn added for bug 6851095
195                 -- End changes for Bug 6828493
196             AND (per.current_employee_flag = 'Y'
197                          OR
198                  per.current_npw_flag = 'Y'); -- FP M CWK
199 
200           END IF ; --IF (nvl(l_future_term_wf_flag,'N') = 'Y') THEN
201           /* End of Changes for Bug 6056112 */
202 
203             ELSIF p_check_id_flag = 'N' THEN
204             x_resource_id := p_resource_id;
205 
206 /* FP M CWK - no need to do this at all since l_sys_per_type is not
207  * used for anything */
208 /*                      SELECT type.system_person_type
209                 INTO   l_sys_per_type
210                 FROM   per_all_people_f per,
211                                per_person_types type
212                 WHERE  per.person_id = x_resource_id
213                         AND    per.person_type_id = type.person_type_id
214             AND    trunc(p_date) between trunc(per.effective_start_date)
215                                 and trunc(per.effective_end_date)
216             AND    (per.current_employee_flag = 'Y' OR -- Added this check for bug#2683266
217                                 per.current_npw_flag = 'Y'); -- FP M CWK */
218 
219                 ELSIF p_check_id_flag = 'A' THEN
220                      IF (p_resource_name IS NULL) THEN
221                         -- Return a null ID since the name is null.
222                         x_resource_id := NULL;
223                      ELSE
224                         -- Find the ID which matches the Name passed
225                         OPEN r_ids;
226                         LOOP
227                            FETCH r_ids INTO l_current_id;
228                            EXIT WHEN r_ids%NOTFOUND;
229                            IF (l_current_id = p_resource_id) THEN
230                               l_id_found_flag := 'Y';
231                               x_resource_id := p_resource_id;
232                            END IF;
233                         END LOOP;
234                         l_num_ids := r_ids%ROWCOUNT;
235                         CLOSE r_ids;
236 
237                         IF (l_num_ids = 0) THEN
238                            -- No IDs for name
239                            RAISE NO_DATA_FOUND;
240                         ELSIF (l_num_ids = 1) THEN
241                            -- Since there is only one ID for the name use it.
242                            x_resource_id := l_current_id;
243 /* FP M CWK - no need to do this at all since l_sys_per_type is not
244  * used for anything */
245 /*                         SELECT type.system_person_type
246                            INTO   l_sys_per_type
247                            FROM   per_all_people_f per,
248                                   per_person_types type
249                            WHERE  per.person_id = x_resource_id
250                            AND    per.person_type_id = type.person_type_id
251                            AND    trunc(p_date) between trunc(per.effective_start_date) and trunc(per.effective_end_date)
252             AND    (per.current_employee_flag = 'Y' OR -- Added this check for bug#2683266
253                                 per.current_npw_flag = 'Y'); -- FP M CWK */
254 
255                         ELSIF (l_id_found_flag = 'N') THEN
256                            -- More than one ID for the name and none of the IDs matched
257                            -- the ID passed in.
258                            RAISE TOO_MANY_ROWS;
259                         END IF;
260                       END IF;
261         END IF;
262         ELSE          -- Find ID since it was not passed.
263             IF (p_resource_name IS NOT NULL) THEN
264 
265         SELECT per.person_id
266                -- type.system_person_type -- FP M CWK
267             INTO   x_resource_id
268                -- l_sys_per_type -- FP M CWK
269             FROM   per_all_people_f per
270                        -- per_person_types type -- FP M CWK
271             WHERE  per.full_name = p_resource_name
272                 -- AND    per.person_type_id = type.person_type_id -- FP M CWK
273         AND    trunc(p_date) between trunc(per.effective_start_date)
274                                          and trunc(per.effective_end_date)
275         AND (p_end_date is null OR (trunc(p_end_date) between trunc(per.effective_start_date) -- 3235018 Added end date condition
276                       and trunc(per.effective_end_date)))
277         AND    (per.current_employee_flag = 'Y' OR /* Added this check for bug#2683266 */
278                         per.current_npw_flag = 'Y'); -- FP M CWK
279 
280             ELSE
281                 x_resource_id := NULL;
282             END IF;
283         END IF;
284 
285 /* Commented for bug#2683266 as person type should not be checked in pa_resource_types table
286    as pa_resource_types does not contain all person_types defined in HR table per_person_types
287 
288         IF l_sys_per_type is not null THEN
289            select resource_type_id
290            into x_resource_type_id
291            from pa_resource_types
292            where resource_type_code = decode(l_sys_per_type,
293                                             'EMP','EMPLOYEE');
294         END IF;
295 */
296     x_resource_type_id := l_resource_type_id; /* Added for bug#2683266 as the earlier select is commented */
297 
298      ELSIF l_resource_type_id = 112 THEN
299 
300      ---------------------
301      -- For type HZ_PARTY
302      ---------------------
303         IF p_resource_id IS NOT NULL AND p_resource_id<>FND_API.G_MISS_NUM THEN
304 
305                 SELECT party_id
306             INTO   x_resource_id
307             FROM   pa_party_resource_details_v hz
308             WHERE  hz.party_id = p_resource_id
309         AND    trunc(p_date) between trunc(hz.start_date)
310                    and trunc(nvl(hz.end_date, to_date('31-12-4712', 'DD-MM-YYYY')));
311 
312         ELSE
313             IF (p_resource_name IS NOT NULL) THEN
314         SELECT party_id
315             INTO   x_resource_id
316             FROM   pa_party_resource_details_v hz
317             WHERE  hz.party_name = p_resource_name
318         AND    trunc(p_date) between trunc(hz.start_date)
319                    and trunc(nvl(hz.end_date, to_date('31-12-4712', 'DD-MM-YYYY')));
320             ELSE
321                 x_resource_id := NULL;
322             END IF;
323 
324         END IF;
325 
326         -- also set the resource_type_id to 112 for HZ_PARTY
327         x_resource_type_id := 112;
328 
329      END IF;    /* after checking the resource_type_id */
330 
331      x_return_status := FND_API.G_RET_STS_SUCCESS;
332 
333  EXCEPTION
334         WHEN NO_DATA_FOUND THEN
335                 x_resource_id := NULL;
336             x_return_status := FND_API.G_RET_STS_ERROR;
337         x_error_message_code := 'PA_RESOURCE_INVALID_AMBIGUOUS';
338         WHEN TOO_MANY_ROWS THEN
339                 x_resource_id := NULL;
340             x_return_status := FND_API.G_RET_STS_ERROR;
341         x_error_message_code := 'PA_MULTIPLE_RESOURCE';
342         WHEN OTHERS THEN
343         --PA_Error_Utils.Set_Error_Stack
344         -- (`pa_resource_utils.check_resourcename_or_id');
345             -- This sets the current program unit name in the
346             -- error stack. Helpful in Debugging
347         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
348                 x_resource_id := NULL;
349 
350  END Check_ResourceName_Or_Id;
351 
352 --
353 --  PROCEDURE
354 --              Get_CRM_Res_id
355 --  PURPOSE
356 --              Returns the CRM Resource_id based on the
357 --              project_player_id
358 
359 --  HISTORY
360 --   27-JUN-2000      P. Bandla       Created
361 
362  PROCEDURE Get_CRM_Res_id(
363     P_PROJECT_PLAYER_ID IN  NUMBER,
364         P_RESOURCE_ID           IN      NUMBER,
365     X_JTF_RESOURCE_ID   OUT NOCOPY NUMBER,  --File.Sql.39 bug 4440895
366         X_RETURN_STATUS     OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
367         X_ERROR_MESSAGE_CODE    OUT NOCOPY VARCHAR2 ) IS --File.Sql.39 bug 4440895
368 
369     l_project_player_id NUMBER := p_project_player_id;
370         l_resource_id       NUMBER := p_resource_id ;
371  BEGIN
372     IF P_PROJECT_PLAYER_ID is null
373     AND P_RESOURCE_ID is not null THEN
374       -- use p_resource_id to get the CRM resource_id
375 
376       select jtf_resource_id
377       into x_jtf_resource_id
378       from pa_resources
379       where resource_id = l_resource_id;
380 
381     ELSIF P_PROJECT_PLAYER_ID is not null
382     AND P_RESOURCE_ID is null THEN
383 
384        -- use p_project_player_id to get the CRM resource_id
385 
386     select a.jtf_resource_id
387     into x_jtf_resource_id
388     from pa_resources a, pa_project_parties  b
389     where a.resource_id = b.resource_id
390     and b.project_party_id = l_project_player_id;
391 
392     ELSIF (P_PROJECT_PLAYER_ID is not null
393     AND P_RESOURCE_ID is not null)
394     OR (P_PROJECT_PLAYER_ID is null
395     AND P_RESOURCE_ID is null) THEN
396 
397        x_jtf_resource_id := null ;
398 
399     END IF;
400 
401        x_return_status := FND_API.G_RET_STS_SUCCESS;
402 
403  EXCEPTION
404         WHEN NO_DATA_FOUND THEN
405             x_jtf_resource_id := null ;
406             x_return_status := FND_API.G_RET_STS_SUCCESS;
407             --x_return_status := FND_API.G_RET_STS_ERROR;
408                     --x_error_message_code := 'PA_CRM_RES_NULL';
409     WHEN OTHERS THEN
410         --PA_Error_Utils.Set_Error_Stack
411         -- (`pa_resource_utils.check_resourcename_or_id');
412             -- This sets the current program unit name in the
413             -- error stack. Helpful in Debugging
414 
415         X_JTF_RESOURCE_ID := NULL ; -- 4537865
416         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
417 
418  END Get_CRM_Res_id;
419 
420  PROCEDURE CHECK_CC_FOR_RESOURCE(
421         P_RESOURCE_ID           IN      NUMBER,
422     P_PROJECT_ID            IN      NUMBER,
423     P_START_DATE            IN      DATE,
424         P_END_DATE              IN      DATE,
425         X_CC_OK                 OUT     NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
426         X_RETURN_STATUS         OUT     NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
427         X_ERROR_MESSAGE_CODE    OUT     NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
428 
429  IS
430     cursor get_org_id_from_resource is
431         select
432         resource_org_id
433         from
434         pa_resources_denorm
435         where
436         resource_id = p_resource_id
437     and     p_start_date between resource_effective_start_date
438                                  and resource_effective_end_date;
439 
440     NULL_INVALID_PARAMS  EXCEPTION;
441     l_prvdr_org_id       NUMBER := NULL;
442 
443  BEGIN
444 
445    -- IF this is a single-org instance, there will be
446    -- no cross-charge setup. Return 'Y' for single-org
447    -- instances.
448 
449    IF PA_UTILS.pa_morg_implemented = 'N' THEN
450        X_CC_OK            := 'Y';
451        X_RETURN_STATUS    := FND_API.G_RET_STS_SUCCESS;
452    ELSE
453     /* Dependency against pa_projects_expend_v v115.14 */
454 
455     open get_org_id_from_resource;
456     fetch get_org_id_from_resource into l_prvdr_org_id;
457     close get_org_id_from_resource;
458 
459     If l_prvdr_org_id IS NULL Then
460          /* A resource identifier was passed that does not
461               * exist in pa_resources_denorm table and is therefore
462               * invalid so raise exception.
463               */
464          raise NULL_INVALID_PARAMS;
465     End If;
466 
467       -- Added the same where clause here as in view pavw168.sql. This is due to      -- Bug # 1478149. Removed the check for project status.
468 
469    -- MOAC Changes: Bug 4363092: removed nvl with org_id
470         select
471         'Y'
472         into
473         X_CC_OK
474         FROM HR_ORGANIZATION_INFORMATION PLE,
475              HR_ORGANIZATION_INFORMATION RLE,
476              pa_project_types_all PT,
477              pa_projects_all P,
478              pa_implementations_all iprv,
479              pa_implementations_all irecv
480         WHERE P.project_type = PT.project_type
481           AND NVL(P.template_flag, 'N') <> 'Y'
482           --Bug2538692 AND pa_security.allow_query(P.project_id) = 'Y'
483           AND ((iprv.business_group_id = irecv.business_group_id
484           and pa_cross_business_grp.IsCrossBGProfile='N')
485            OR pa_cross_business_grp.IsCrossBGProfile ='Y')
486           -- bug 8967761 .. below 2 are changed to remove IS NULL
487           --AND (irecv.org_id IS NULL OR irecv.org_id = P.org_id)
488           --AND (PT.org_id IS NULL or PT.org_id = P.org_id)
489           AND (irecv.org_id = P.org_id)
490           AND (PT.org_id = P.org_id)
491           AND PT.project_type <> 'AWARD_PROJECT'
492           AND nvl(PT.cc_prvdr_flag, 'N') <> 'Y'
493           AND PLE.organization_id (+) = iprv.org_id
494           AND PLE.org_information_context (+) = 'Operating Unit Information'
495           AND RLE.organization_id (+) = irecv.org_id
496           AND RLE.org_information_context (+) = 'Operating Unit Information'
497           AND ( P.org_id = iprv.org_id
498               OR
499               ( PLE.org_information2 = RLE.org_information2
500                 AND ( EXISTS ( SELECT null FROM PA_CC_ORG_RELATIONSHIPS CO
501                                WHERE CO.prvdr_org_id = iprv.org_id
502                                AND   CO.recvr_org_id = irecv.org_id
503                                AND   CO.prvdr_allow_cc_flag = 'Y')
504                       OR
505                       (iprv.cc_allow_iu_flag = 'Y'
506                        AND NOT EXISTS ( SELECT null FROM
507                                         PA_CC_ORG_RELATIONSHIPS CO
508                                         WHERE CO.prvdr_org_id = iprv.org_id
509                                         AND   CO.recvr_org_id = irecv.org_id
510                                         AND   CO.prvdr_allow_cc_flag = 'N')
511                        )
512                      )
513                )
514               OR
515               ( PLE.org_information2 <> RLE.org_information2
516                 AND PT.project_type_class_code <> 'CAPITAL'
517                 AND EXISTS ( SELECT null FROM PA_CC_ORG_RELATIONSHIPS CO
518                              WHERE CO.prvdr_org_id = iprv.org_id
519                              AND   CO.recvr_org_id = irecv.org_id
520                              AND   CO.prvdr_allow_cc_flag = 'Y'
521                              AND  (( CO.prvdr_project_id IS NOT NULL
522                                    AND CO.vendor_site_id IS NOT NULL
523                                    AND CO.cross_charge_code  = 'I')
524                                    OR CO.cross_charge_code  = 'N' )
525                              )
526                 )
527               )
528               AND P.project_id = p_project_id
529               AND     iprv.org_id = l_prvdr_org_id;
530    END IF; /* If multiorg implemented */
531 
532  EXCEPTION
533     WHEN NO_DATA_FOUND THEN
534         /* This exception should only occur if the provider org id
535                  * does not exist in pa_projects_expend_v in which case the
536                  * Cross Charge condition is not met and the employee/resource
537                  * cannot be used for the project which is having resources
538                  * allocated to it.
539                  */
540         X_CC_OK := 'N';
541         x_return_status := NULL;
542         x_error_message_code := NULL;
543     WHEN NULL_INVALID_PARAMS THEN
544                 /*
545                  * When p_resource_id passed in is invalid.
546          */
547                 x_return_status := FND_API.G_RET_STS_ERROR;
548                 x_error_message_code := 'PA_RS_OU_DATE_NULL';
549     WHEN OTHERS THEN
550         X_CC_OK := NULL ; -- 4537865
551         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
552         x_error_message_code := NULL;
553         RAISE ; -- 4537865
554  END CHECK_CC_FOR_RESOURCE;
555 
556 --
557 --  PROCEDURE
558 --              Check_Resource_Belongs_ExpOrg
559 --  PURPOSE
560 --              This procedure does the following
561 --              For the given Resource Id,
562 --              checks if that resource
563 --      belongs to an expenditure organization
564 --  HISTORY
565 --   22-AUG-2000      P.Bandla       Created
566 --   11-APR-2001      virangan       Removed join to pa_c_elig_resource_v
567 --                                   and added joins to base table
568 --                                   for performance tuning BUG 1713739
569 --   24-APR-2001      virangan       Changed back to cursor logic for the check
570 --
571  PROCEDURE CHECK_RES_BELONGS_EXPORG(
572                 p_resource_id          IN      NUMBER,
573                 x_valid            OUT     NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
574                 x_return_status        OUT     NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
575                 x_error_message_code   OUT     NOCOPY VARCHAR2)  --File.Sql.39 bug 4440895
576  IS
577     l_exist VARCHAR2(1):= null;
578     l_future_resource VARCHAR2(1);
579     l_future_rehire VARCHAR2(1); -- added for bug 8988264
580     l_effective_date DATE;
581     -- Bug 8567601
582     cursor cur_exist(l_res_id in NUMBER, l_date IN date) is
583          select 'X'
584              from dual
585              where exists (select res.resource_id
586                            from   pa_resources_denorm res,
587                                   pa_all_organizations org
588                            where  org.pa_org_use_type  = 'EXPENDITURES'
589                            and    org.inactive_date    IS NULL
590                            and    org.organization_id  = res.resource_organization_id
591                            and    res.resource_id      = p_resource_id
592                            and    TRUNC(l_date) between TRUNC(res.resource_effective_start_date) and TRUNC(res.resource_effective_end_date));
593 
594  BEGIN
595 
596     x_return_status := FND_API.G_RET_STS_SUCCESS;
597 
598     l_future_resource := is_future_resource( p_resource_id);
599 
600     --bug 8988264 : skkoppul
601     l_future_rehire := is_future_rehire(p_resource_id);
602 
603 --Bug#10199073
604     IF l_future_resource = 'Y'    THEN
605   l_effective_date := get_resource_start_date( p_resource_id);
606 ELSE IF  (l_future_rehire = 'Y' AND l_future_resource = 'N')     THEN
607         l_effective_date := get_resource_start_date_rehire(p_resource_id);
608      ELSIF (l_future_rehire = 'Y' AND l_future_resource = 'Y') THEN      --bug 9539388
609      l_effective_date := get_resource_start_date_rehire( p_resource_id);
610      else
611         l_effective_date := sysdate;
612     END IF;
613     END IF ;
614 	--Bug#10199073
615 
616     open cur_exist(p_resource_id, l_effective_date);
617     fetch cur_exist into l_exist;
618     close cur_exist;
619 
620     if l_exist is not null then
621         x_valid := 'Y';
622     else
623         x_valid := 'N';
624     end if;
625     x_return_status := FND_API.G_RET_STS_SUCCESS;
626 
627  EXCEPTION
628         WHEN NO_DATA_FOUND THEN
629       x_return_status := FND_API.G_RET_STS_ERROR;
630           x_error_message_code := 'PA_RES_NOT_EXPORG';
631         WHEN OTHERS THEN
632           --PA_Error_Utils.Set_Error_Stack
633           -- (`pa_job_utils.check_resource_belongs_exporg');
634       -- This sets the current program unit name in the
635           -- error stack. Helpful in Debugging
636 
637       x_valid := NULL ; -- 4537865
638           x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
639       x_error_message_code := NULL;
640 
641  END CHECK_RES_BELONGS_EXPORG;
642 
643 
644 --
645 --  PROCEDURE
646 --              Check_Resource_Belongs_ExpOrg
647 --  PURPOSE
648 --              This is a overloaded procedure which does the following
649 --              For the given Resource Id, Resource Start Date and Resource End Date
650 --              checks if that resource
651 --              belongs to an expenditure organization
652 --  HISTORY
653 --   01-JAN-2009      asahoo       Created
654 --
655  PROCEDURE CHECK_RES_BELONGS_EXPORG(
656                 p_resource_id          IN      NUMBER,
657                 p_start_date_active    IN      DATE,
658                 p_end_date_active      IN      DATE,
659                 x_valid                OUT     NOCOPY VARCHAR2,
660                 x_return_status        OUT     NOCOPY VARCHAR2,
661                 x_error_message_code   OUT     NOCOPY VARCHAR2)
662  IS
663     l_exist VARCHAR2(1):= null;
664 
665     cursor cur_exist(l_res_id IN NUMBER,
666                      l_start_date_active IN DATE,
667                      l_end_date_active IN DATE) is
668          select 'X'
669              from dual
670              where exists (select res.resource_id
671                            from   pa_resources_denorm res,
672                                   pa_all_organizations org
673                            where  org.pa_org_use_type  = 'EXPENDITURES'
674                            and    org.inactive_date    IS NULL
675                            and    org.organization_id  = res.resource_organization_id
676                            and    res.resource_id      = p_resource_id
677                            and    l_start_date_active between get_resource_start_date(p_resource_id) and get_resource_end_date(p_resource_id)
678                            and    l_end_date_active <=  get_resource_end_date(p_resource_id));
679 						   -- modified this cursor for bug#9233998
680 
681  BEGIN
682 
683     x_return_status := FND_API.G_RET_STS_SUCCESS;
684 
685     open cur_exist(p_resource_id, p_start_date_active, p_end_date_active);
686     fetch cur_exist into l_exist;
687     close cur_exist;
688 
689     if l_exist is not null then
690         x_valid := 'Y';
691     else
692         x_valid := 'N';
693     end if;
694     x_return_status := FND_API.G_RET_STS_SUCCESS;
695 
696  EXCEPTION
697         WHEN NO_DATA_FOUND THEN
698           x_return_status := FND_API.G_RET_STS_ERROR;
699           x_error_message_code := 'PA_RES_NOT_EXPORG';
700         WHEN OTHERS THEN
701           x_valid := NULL ;
702           x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
703           x_error_message_code := NULL;
704 
705  END CHECK_RES_BELONGS_EXPORG;
706 --
707 -- This procedure is called from form PAXRESSC
708 --
709 PROCEDURE set_global_variables( p_selected_flag IN VARCHAR2
710                                ,p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE
711                                ,p_version_id    IN PER_ORG_STRUCTURE_ELEMENTS.ORG_STRUCTURE_VERSION_ID%TYPE
712                                ,p_start_org_id  IN PER_ORG_STRUCTURE_ELEMENTS.ORGANIZATION_ID_PARENT%TYPE
713                               )
714 IS
715 BEGIN
716 
717   G_SELECTED_FLAG := p_selected_flag;
718   G_PERSON_ID     := p_person_id;
719   G_VERSION_ID    := p_version_id;
720   G_START_ORG_ID  := p_start_org_id;
721 
722 END set_global_variables;
723 
724 --
725 -- This Function is used by the view pa_org_authority_v.
726 --
727 FUNCTION get_selected_flag RETURN VARCHAR2
728 IS
729 BEGIN
730  RETURN G_SELECTED_FLAG;
731 END get_selected_flag;
732 
733 --
734 -- This Function is used by the view pa_org_authority_v.
735 --
736 FUNCTION get_person_id RETURN PA_EMPLOYEES.PERSON_ID%TYPE
737 IS
738 BEGIN
739  RETURN G_PERSON_ID;
740 END get_person_id;
741 
742 --
743 -- This Function is used by the view pa_org_authority_v.
744 --
745 FUNCTION get_version_id RETURN PER_ORG_STRUCTURE_ELEMENTS.ORG_STRUCTURE_VERSION_ID%TYPE
746 IS
747 BEGIN
748  RETURN G_VERSION_ID;
749 END get_version_id;
750 
751 --
752 -- This Function is used by the view pa_org_authority_v.
753 --
754 FUNCTION get_start_org_id RETURN PER_ORG_STRUCTURE_ELEMENTS.ORGANIZATION_ID_PARENT%TYPE
755 IS
756 BEGIN
757  RETURN G_START_ORG_ID;
758 END get_start_org_id;
759 
760 FUNCTION get_period_date RETURN DATE
761 IS
762 BEGIN
763  RETURN G_PERIOD_DATE;
764 END;
765 --
766 -- This Procedure, receives person_id, org_id and populates the flags corresponding the
767 -- check-boxes in the form. (Used in PAXRESSC)
768 --
769 
770 PROCEDURE populate_role_flags( p_person_id       IN PA_EMPLOYEES.PERSON_ID%TYPE
771                               ,p_org_id         IN PER_ORG_STRUCTURE_ELEMENTS.ORGANIZATION_ID_PARENT%TYPE
772                               ,x_res_aut_flag   OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
773                               ,x_proj_aut_flag  OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
774                               ,x_prim_ctct_flag OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
775                   ,x_frcst_aut_flag   OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
776                               ,x_frcst_prim_ctct_flag OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
777                   ,x_utl_aut_flag  OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
778                              )
779 IS
780   l_role_id FND_GRANTS.MENU_ID%TYPE;
781 BEGIN
782   x_res_aut_flag   := 'N';
783   x_proj_aut_flag  := 'N';
784   x_prim_ctct_flag := 'N';
785   x_frcst_aut_flag   := 'N';
786   x_utl_aut_flag  := 'N';
787   x_frcst_prim_ctct_flag := 'N';
788 
789   l_role_id := pa_security_pvt.get_menu_id('PA_PRM_RES_AUTH');
790   IF pa_security_pvt.is_role_exists( 'ORGANIZATION'
791                   ,'INSTANCE'
792                   ,l_role_id
793                   ,p_org_id
794                   ,p_person_id
795                  ) THEN
796     x_res_aut_flag := 'Y';
797   END IF;
798 
799   l_role_id := pa_security_pvt.get_menu_id('PA_PRM_PROJ_AUTH');
800   IF pa_security_pvt.is_role_exists( 'ORGANIZATION'
801                   ,'INSTANCE'
802                   ,l_role_id
803                   ,p_org_id
804                   ,p_person_id
805                  )
806   THEN
807     x_proj_aut_flag := 'Y';
808   END IF;
809 
810   --changed role name to Resource Primary Contact
811   l_role_id := pa_security_pvt.get_menu_id('PA_PRM_RES_PRMRY_CONTACT');
812   IF pa_security_pvt.is_role_exists( 'ORGANIZATION'
813                   ,'INSTANCE'
814                   ,l_role_id
815                   ,p_org_id
816                   ,p_person_id
817                  )
818   THEN
819     x_prim_ctct_flag := 'Y';
820   END IF;
821 
822 
823 /*6519194 for enhancement*/
824 /*  l_role_id := pa_security_pvt.get_menu_id('PA_PRM_FCST_AUTH');
825   IF pa_security_pvt.is_role_exists( 'ORGANIZATION'
826                   ,'INSTANCE'
827                   ,l_role_id
828                   ,p_org_id
829                   ,p_person_id) THEN
830              x_frcst_aut_flag := 'Y';
831   END IF;
832 
833   l_role_id := pa_security_pvt.get_menu_id('PA_PRM_FCST_PRMRY_CONTACT');
834   IF pa_security_pvt.is_role_exists( 'ORGANIZATION'
835             ,'INSTANCE'
836                     ,l_role_id
837             ,p_org_id
838             ,p_person_id) THEN
839               x_frcst_prim_ctct_flag := 'Y';
840   END IF;
841 */
842   l_role_id := pa_security_pvt.get_menu_id('PA_PRM_UTL_AUTH');
843   IF pa_security_pvt.is_role_exists( 'ORGANIZATION'
844                   ,'INSTANCE'
845                   ,l_role_id
846                   ,p_org_id
847                   ,p_person_id) THEN
848             x_utl_aut_flag := 'Y';
849   END IF;
850 EXCEPTION -- 4537865
851 WHEN OTHERS THEN
852 
853 -- Reset all OUT params
854   x_res_aut_flag   := 'N';
855   x_proj_aut_flag  := 'N';
856   x_prim_ctct_flag := 'N';
857   x_frcst_aut_flag   := 'N';
858   x_utl_aut_flag  := 'N';
859   x_frcst_prim_ctct_flag := 'N';
860 
861 -- Populate the Error Message
862   Fnd_Msg_Pub.add_exc_msg
863                    ( p_pkg_name        => 'pa_resource_utils'
864                     , p_procedure_name  => 'populate_role_flags'
865                     , p_error_text      => SUBSTRB(SQLERRM,1,100));
866 
867 -- Raise the Error
868     RAISE;
869 END populate_role_flags;
870 
871 FUNCTION get_organization_name(p_org_id IN HR_ORGANIZATION_UNITS.ORGANIZATION_ID%TYPE)
872             RETURN HR_ORGANIZATION_UNITS.NAME%TYPE
873 IS
874   l_org_name HR_ORGANIZATION_UNITS.NAME%TYPE;
875 BEGIN
876 -- 4882876 : Adding caching logic
877 IF G_ORGANIZATION_ID IS NULL OR G_ORGANIZATION_ID <> p_org_id THEN
878 	G_ORGANIZATION_ID := p_org_id;
879 	SELECT name
880 	INTO l_org_name
881 	FROM hr_organization_units
882 	WHERE organization_id = p_org_id;
883 	G_ORGANIZATION_NAME := l_org_name;
884 ELSIF p_org_id IS NULL THEN  -- Bug 9156671
885   G_ORGANIZATION_ID := NULL;
886   l_org_name := NULL;
887 ELSE
888 	l_org_name := G_ORGANIZATION_NAME;
889 END IF;
890 
891    RETURN l_org_name;
892  EXCEPTION
893    WHEN OTHERS THEN
894      RAISE;
895 END get_organization_name;
896 
897 --
898 -- This procedure is used to insert a INSTANCE/SET into fnd_grants
899 --
900 PROCEDURE insert_grant( p_person_id  IN NUMBER
901                        ,p_org_id     IN NUMBER
902                        ,p_role_name  IN VARCHAR2
903                        ,x_return_status OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
904                       )
905 IS
906 
907 l_grant_id      FND_GRANTS.GRANT_GUID%TYPE;
908 l_object_name   FND_OBJECTS.OBJ_NAME%TYPE;
909 l_role_id       FND_GRANTS.MENU_ID%TYPE;
910 l_return_status VARCHAR2(30);
911 l_msg_data      VARCHAR2(2000); -- Changed from 30 to 2000 to avoid ora 6502 error
912 l_msg_count     NUMBER;
913 l_set_name      FND_OBJECT_INSTANCE_SETS.INSTANCE_SET_NAME%TYPE;
914 l_set_id        FND_GRANTS.INSTANCE_SET_ID%TYPE;
915 BEGIN
916 l_role_id := PA_SECURITY_PVT.get_menu_id(p_role_name);
917 --
918 -- At this point, the global variable for person_id cannot be used,
919 -- because, the global variable is populated - when the FIND button is
920 -- pressed.
921 -- But the resource name could have been entered - AFTER pressing the FIND button.
922 --
923 IF p_role_name = 'PA_PRM_RES_AUTH' THEN
924   l_object_name := 'PA_RESOURCES';
925   l_set_name    := 'PA_RESOURCE_AUTHORITY';
926 ELSIF p_role_name = 'PA_PRM_PROJ_AUTH' THEN
927   l_object_name := 'PA_PROJECTS';
928   l_set_name    := 'PA_PROJECT_AUTHORITY';
929 END IF;
930 l_set_id := pa_security_pvt.get_instance_set_id(l_set_name);
931 
932 --
933 -- First, check whether there is a SET record this role in the table.
934 -- IF NO,
935 --   Create SET record.
936 -- END IF.
937 -- CREATE the INSTANCE record.
938 --
939 
940 --
941 -- When selected_flag is 'O' its possible that the user may try to grant a
942 -- role to a resource , which the resource already has. In that case, the following
943 -- check is necessary.
944 --
945    IF
946       --G_SELECTED_FLAG = 'O' AND
947       pa_security_pvt.is_role_exists( 'ORGANIZATION'
948                                          ,'INSTANCE'
949                                          ,l_role_id
950                                          ,p_org_id
951                                          ,p_person_id
952                                         )
953    THEN
954     --Role already exists.
955      return;
956    END IF;
957 
958         IF p_role_name <> 'PA_PRM_RES_PRMRY_CONTACT' AND
959 /*        p_role_name <> 'PA_PRM_FCST_AUTH' AND
960         p_role_name <> 'PA_PRM_FCST_PRMRY_CONTACT' AND*/ /*6519194 for enhancement*/
961         p_role_name <> 'PA_PRM_UTL_AUTH' AND
962             NOT pa_security_pvt.is_role_exists(p_object_name   => l_object_name
963                                                ,p_object_key_type  => 'INSTANCE_SET'
964                                                ,p_role_id          => l_role_id
965                                                ,p_object_key       => l_set_id
966                                                ,p_party_id         => p_person_id)
967         THEN
968             --Create the SET record.
969             pa_security_pvt.grant_org_authority
970               (
971                 p_commit           => NULL
972                ,p_debug_mode       => NULL
973            ,p_project_role_id  => NULL
974                ,p_menu_name        => p_role_name
975                ,p_object_name      => l_object_name
976                ,p_object_key_type  => 'INSTANCE_SET'
977                ,p_object_key       => l_set_id
978                ,p_party_id         => p_person_id
979                ,p_source_type      => 'PERSON'
980                ,p_start_date       => SYSDATE
981                ,p_end_date         => NULL
982                ,x_grant_guid         => l_grant_id
983                ,x_return_status    => l_return_status
984                ,x_msg_count        => l_msg_count
985                ,x_msg_data         => l_msg_data
986              );
987 
988             IF l_return_status <> fnd_api.g_ret_sts_success
989             THEN
990               x_return_status := l_return_status;
991               return;
992             END IF;
993         END IF;
994 
995         --Create the INSTANCE record.
996         pa_security_pvt.grant_org_authority
997           (
998             p_commit           => NULL
999            ,p_debug_mode       => NULL
1000            ,p_project_role_id  => NULL
1001            ,p_menu_name        => p_role_name
1002            ,p_object_name      => 'ORGANIZATION'
1003            ,p_object_key_type  => 'INSTANCE'
1004            ,p_object_key       => p_org_id
1005            ,p_party_id         => p_person_id
1006            ,p_source_type      => 'PERSON'
1007            ,p_start_date       => SYSDATE
1008            ,p_end_date         => NULL
1009            ,x_grant_guid         => l_grant_id
1010            ,x_return_status    => l_return_status
1011            ,x_msg_count        => l_msg_count
1012            ,x_msg_data         => l_msg_data
1013           );
1014           IF l_return_status <> 'S'
1015           THEN
1016             x_return_status := l_return_status;
1017             return;
1018           END IF;
1019 
1020 COMMIT;
1021 --4537865
1022 EXCEPTION
1023 WHEN OTHERS THEN
1024     x_return_status :=  Fnd_Api.G_RET_STS_UNEXP_ERROR;
1025     Fnd_Msg_Pub.add_exc_msg
1026                    ( p_pkg_name        => 'pa_resource_utils'
1027                     , p_procedure_name  => 'insert_grant'
1028                     , p_error_text      => SUBSTRB(SQLERRM,1,100));
1029     RAISE;
1030 END insert_grant;
1031 
1032 --
1033 -- This procedure is used to delete a INSTANCE/SET from fnd_grants
1034 --
1035 PROCEDURE delete_grant( p_person_id  IN NUMBER
1036                         ,p_org_id     IN NUMBER
1037                         ,p_role_name  IN VARCHAR2
1038                         ,x_return_status OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
1039                       )
1040 IS
1041 
1042 l_set_id        FND_GRANTS.INSTANCE_SET_ID%TYPE;
1043 l_set_name      FND_OBJECT_INSTANCE_SETS.INSTANCE_SET_NAME%TYPE;
1044 l_object_name   FND_OBJECTS.OBJ_NAME%TYPE;
1045 l_role_id       FND_GRANTS.MENU_ID%TYPE;
1046 l_return_status VARCHAR2(30);
1047 l_msg_data      VARCHAR2(2000); -- Changed from 30 to 2000 to avoid ora 6502 error
1048 l_msg_count     NUMBER;
1049 
1050 BEGIN
1051 
1052 IF p_role_name = 'PA_PRM_RES_AUTH' THEN
1053   l_object_name := 'PA_RESOURCES';
1054   l_set_name := 'PA_RESOURCE_AUTHORITY';
1055 ELSIF p_role_name = 'PA_PRM_PROJ_AUTH' THEN
1056   l_object_name := 'PA_PROJECTS';
1057   l_set_name := 'PA_PROJECT_AUTHORITY';
1058 END IF;
1059 
1060 --
1061 -- At this point, the global variable for person_id cannot be used,
1062 -- because, the global variable is populated - when the FIND button is
1063 -- pressed.
1064 -- But the resource name could have been entered - AFTER pressing the FIND button.
1065 --
1066 
1067 --
1068 -- delete_grant will be called only when G_SELECTED_FLAG is 'R' or 'B'
1069 --
1070 
1071 --Call API to delete INSTANCE record.
1072 
1073  pa_security_pvt.revoke_role
1074   (
1075    p_commit             => FND_API.G_TRUE
1076    ,p_debug_mode        => NULL
1077    ,p_project_role_id   => NULL
1078    ,p_menu_name         => p_role_name
1079    ,p_object_name       => 'ORGANIZATION'
1080    ,p_object_key_type   => 'INSTANCE'
1081    ,p_object_key        => p_org_id
1082    ,p_party_id          => p_person_id
1083    ,p_source_type       => 'PERSON'
1084    ,x_return_status     => l_return_status
1085    ,x_msg_count         => l_msg_count
1086    ,x_msg_data          => l_msg_data
1087   );
1088   IF l_return_status <> 'S'
1089   THEN
1090     x_return_status := l_return_status;
1091     return;
1092   END IF;
1093 
1094 
1095 --Check if there's any more INSTANCE record available for the combination.
1096 --Call API to delete SET record.
1097 
1098 --Added the check if role = Resource Authority or Project Authority
1099 --then delete the SET record if no more INSTANCE records exist.
1100 
1101   IF ((p_role_name = 'PA_PRM_RES_AUTH') or (p_role_name = 'PA_PRM_PROJ_AUTH')) THEN
1102     l_role_id := PA_SECURITY_PVT.get_menu_id(p_role_name);
1103     IF NOT pa_security_pvt.is_role_exists ( p_object_name      => 'ORGANIZATION'
1104                        ,p_object_key_type  => 'INSTANCE'
1105                        ,p_role_id          => l_role_id
1106                        ,p_object_key       => NULL
1107                        ,p_party_id         => p_person_id
1108                       ) THEN
1109 
1110       -- Delete the INSTANCE_SET record.
1111       l_set_id := pa_security_pvt.get_instance_set_id(l_set_name);
1112       pa_security_pvt.revoke_role(
1113         p_commit             => FND_API.G_TRUE
1114         ,p_debug_mode        => NULL
1115             ,p_project_role_id   => NULL
1116             ,p_menu_name         => p_role_name
1117         ,p_object_name       => l_object_name
1118         ,p_object_key_type   => 'INSTANCE_SET'
1119         ,p_object_key        => l_set_id
1120         ,p_party_id          => p_person_id
1121         ,p_source_type       => 'PERSON'
1122         ,x_return_status     => l_return_status
1123         ,x_msg_count         => l_msg_count
1124         ,x_msg_data          => l_msg_data);
1125 
1126       IF l_return_status <> 'S'
1127       THEN
1128         x_return_status := l_return_status;
1129         return;
1130       END IF;
1131     END IF;
1132   END IF;
1133 COMMIT;
1134 --4537865
1135 EXCEPTION
1136 WHEN OTHERS THEN
1137         x_return_status :=  Fnd_Api.G_RET_STS_UNEXP_ERROR;
1138         Fnd_Msg_Pub.add_exc_msg
1139                    ( p_pkg_name        => 'pa_resource_utils'
1140                     , p_procedure_name  => 'delete_grant'
1141                     , p_error_text      => SUBSTRB(SQLERRM,1,100));
1142         RAISE;
1143 END delete_grant;
1144 
1145 
1146 
1147 FUNCTION GetValJobGradeId (P_Job_Id     IN per_jobs.job_id%TYPE,
1148                            P_Job_Grp_Id IN  per_jobs.job_group_id%TYPE)
1149                                         RETURN per_valid_grades.grade_id%type
1150 
1151 IS
1152 
1153         /*CURSOR grades_sequences is -- commented out for perf bug 4887375
1154         select
1155                 distinct pg.grade_id,pg.sequence
1156         from
1157                 per_job_groups pjg,
1158                 per_grades pg,
1159                 per_valid_grades pvg
1160         where
1161                 pjg.master_flag = 'Y'
1162         and     pjg.job_group_id = P_Job_Grp_Id
1163         and     pvg.job_id = P_Job_Id
1164         and     pg.grade_id = pvg.grade_id
1165     and     trunc(sysdate) between pvg.date_from and nvl(pvg.date_to,trunc(sysdate))
1166        UNION
1167         select
1168                 distinct pg.grade_id,pg.sequence
1169         from
1170                 per_valid_grades pvg,
1171                 pa_job_relationships pjr,
1172                 per_job_groups pjg,
1173                 per_grades pg
1174         where
1175                 pjg.master_flag = 'Y'
1176         and     pjr.from_job_id = P_Job_Id
1177         and     pjr.to_job_id = pvg.job_id
1178         and     pjr.to_job_group_id = pjg.job_group_id
1179         and     pg.grade_id = pvg.grade_id
1180         and     trunc(sysdate) between pvg.date_from and nvl(pvg.date_to,trunc(sysdate))
1181        UNION
1182         select
1183                 distinct pg.grade_id,pg.sequence
1184         from
1185                 per_valid_grades pvg,
1186                 pa_job_relationships pjr,
1187                 per_job_groups pjg,
1188                 per_grades pg
1189         where
1190                 pjg.master_flag = 'Y'
1191         and     pjr.to_job_id = P_Job_Id
1192         and     pjr.from_job_id = pvg.job_id
1193         and     pjr.from_job_group_id = pjg.job_group_id
1194         and     pg.grade_id = pvg.grade_id
1195         and     trunc(sysdate) between pvg.date_from and nvl(pvg.date_to,trunc(sysdate))
1196        UNION
1197         select
1198                 distinct pg.grade_id,pg.sequence
1199         from
1200                 per_job_groups pjg,
1201                 per_grades pg,
1202                 per_valid_grades pvg
1203         where   pjg.master_flag = 'N'
1204         and     pjg.job_group_id = P_Job_Grp_Id
1205         and     pvg.job_id = P_Job_Id
1206         and     pg.grade_id = pvg.grade_id
1207         and     not exists (select null
1208                             from per_job_groups
1209                             where master_flag = 'Y')
1210         and     trunc(sysdate) between pvg.date_from and nvl(pvg.date_to,trunc(sysdate));*/
1211 
1212     l_max_seq per_grades.sequence%TYPE := NULL;
1213     l_grade_id per_grades.grade_id%TYPE := NULL;
1214     --grades_seq grades_sequences%ROWTYPE;
1215 
1216 BEGIN
1217     /* This function is not used. comment it out. perf bug 4887375
1218     open grades_sequences;
1219     LOOP
1220         fetch grades_sequences into grades_seq;
1221         EXIT WHEN grades_sequences%NOTFOUND;
1222 
1223         IF l_max_seq IS NULL THEN
1224             l_max_seq := grades_seq.sequence;
1225             l_grade_id := grades_seq.grade_id;
1226         ELSIF l_max_seq < grades_seq.sequence THEN
1227             l_max_seq := grades_seq.sequence;
1228             l_grade_id := grades_seq.grade_id;
1229         END IF;
1230 
1231     END LOOP;
1232 
1233     close grades_sequences;*/
1234     return ( l_grade_id );
1235 
1236 EXCEPTION
1237     WHEN OTHERS THEN
1238         RAISE;
1239 
1240 END GetValJobGradeId;
1241 
1242 
1243 /* --------------------------------------------------------------------
1244 Procedure: GetToJobId
1245 PURPOSE:  This procedure returns the job_id from the job mapping table.
1246           If the job_group_ids are same, it returns the same job id
1247           as what is passed in (does not looking into the mapping table
1248           since there will be no mapping)
1249 -------------------------------------------------------------------- */
1250 PROCEDURE GetToJobId (P_From_Forecast_JobGrpId IN per_jobs.job_group_id%TYPE,
1251                       P_From_JobId IN per_jobs.job_id%TYPE,
1252                       P_To_Proj_Cost_JobGrpId IN per_jobs.job_group_id%TYPE,
1253                       X_To_JobId OUT NOCOPY per_jobs.job_id%TYPE )  --File.Sql.39 bug 4440895
1254 IS
1255 
1256 BEGIN
1257 
1258         IF P_From_Forecast_JobGrpId = P_To_Proj_Cost_JobGrpId THEN
1259            X_To_JobId := P_From_JobId;
1260         ELSE
1261           select to_job_id
1262           into X_To_JobId
1263           from pa_job_relationships_view
1264           where from_job_group_id = P_From_Forecast_JobGrpId
1265           and   to_job_group_id = P_To_Proj_Cost_JobGrpId
1266           and   from_job_id = P_From_JobId;
1267         END IF;
1268 
1269 EXCEPTION
1270     WHEN NO_DATA_FOUND THEN
1271         X_To_JobId := NULL;
1272         WHEN OTHERS THEN
1273         X_To_JobId :=  NULL ; --4537865
1274         -- RAISE; Commented RAISE per Review Comment from Rajnish : 4537865
1275 
1276 END GetToJobId;
1277 
1278 /* --------------------------------------------------------------------
1279 Procedure: GetToJobName
1280 PURPOSE:  This procedure returns the job name from the job mapping table.
1281           If the job_group_ids are same, it returns the job name
1282           of the passed in job_id (from the per_jobs_table)
1283 -------------------------------------------------------------------- */
1284 PROCEDURE GetToJobName (P_From_Forecast_JobGrpId IN per_jobs.job_group_id%TYPE,
1285                         P_From_JobId IN per_jobs.job_id%TYPE,
1286                         P_To_Proj_Cost_JobGrpId IN per_jobs.job_group_id%TYPE,
1287                 X_To_JobName OUT NOCOPY per_jobs.name%TYPE) --File.Sql.39 bug 4440895
1288 IS
1289 
1290 BEGIN
1291 
1292         IF P_From_Forecast_JobGrpId = P_To_Proj_Cost_JobGrpId THEN
1293            SELECT name
1294            INTO   X_To_JobName
1295            FROM   per_jobs
1296            WHERE  job_id = P_From_JobId
1297            AND ROWNUM = 1;
1298         ELSE
1299            select to_job_name
1300            into X_To_JobName
1301            from pa_job_relationships_view
1302            where from_job_group_id = P_From_Forecast_JobGrpId
1303            and   to_job_group_id = P_To_Proj_Cost_JobGrpId
1304            and   from_job_id = P_From_JobId;
1305         END IF;
1306 
1307 EXCEPTION
1308         WHEN NO_DATA_FOUND THEN
1309                 X_To_JobName := NULL;
1310         WHEN OTHERS THEN
1311         X_To_JobName := NULL; -- 4537865
1312                 RAISE;
1313 
1314 
1315 End GetToJobName;
1316 
1317 
1318 --
1319 --  PROCEDURE
1320 --              get_resource_analyst
1321 --  PURPOSE
1322 --              This procedure does the following
1323 --              If Person Id is passed ite retrives the corresponding
1324 --              resource analyst Id ,Resource Analyst Name,Primary contact Id ,
1325 --              Name.
1326 --  HISTORY
1327 --   25-SEP-2000      R Iyengar
1328 
1329 PROCEDURE get_resource_analyst
1330                           (P_PersonId             IN NUMBER,
1331                            P_ResourceIdTab        OUT NOCOPY PLSQLTAB_INTARRAY,
1332                            P_ResourceAnalystTab   OUT NOCOPY PLSQLTAB_NAMEARRAY,
1333                            P_PrimaryContactId     OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1334                            P_PrimaryContactName   OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1335                            X_return_Status        OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1336                            X_error_message_code   OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
1337 
1338         v_validated     VARCHAR2(1);
1339         v_orgid         per_all_assignments_f.organization_id%TYPE;
1340         v_roleid        fnd_grants.menu_id%TYPE;
1341         v_objid         fnd_grants.object_id%TYPE;
1342         v_resid         fnd_grants.grantee_key%TYPE;
1343         v_objname       VARCHAR2(25) := 'ORGANIZATION';
1344         v_rolename      VARCHAR2(30) := 'PA_PRM_RES_AUTH';
1345         v_primrolename  VARCHAR2(30) := 'PA_PRM_RES_PRMRY_CONTACT';
1346         v_primroleid     fnd_grants.menu_id%TYPE;
1347         PersonException EXCEPTION;
1348         missing_role    EXCEPTION;
1349         j               NUMBER;
1350 
1351         cursor analystid(objid  fnd_grants.object_id%TYPE,
1352                      orgid  per_all_assignments_f.organization_id%TYPE,
1353                      roleid fnd_grants.menu_id%TYPE ) is
1354                     SELECT  distinct per.person_id
1355                     FROM   fnd_grants fg, wf_roles wfr, per_all_people_f per
1356                     WHERE  fg.object_id = objid
1357                     AND    fg.instance_pk1_value = TO_CHAR(orgid)
1358                     AND    fg.menu_id = roleid
1359                     AND    fg.instance_type = 'INSTANCE'
1360                     AND fg.grantee_key    = wfr.name
1361                     AND wfr.orig_system    = 'HZ_PARTY'
1362                     AND per.party_id = wfr.orig_system_id
1363                     AND sysdate between per.effective_start_date and
1364                                         per.effective_end_date
1365                     AND    trunc(SYSDATE) BETWEEN trunc(fg.start_date)
1366                                   AND     trunc(NVL(fg.end_date, SYSDATE+1));
1367 
1368 BEGIN
1369 
1370         x_return_status := FND_API.G_RET_STS_SUCCESS;
1371 
1372         -- Validate the PersonId
1373 
1374         BEGIN
1375 
1376             SELECT 'Y'
1377             INTO  v_validated
1378             FROM  per_all_people_f -- Bug 4684198 - use base table not view
1379             WHERE person_id = P_PersonId
1380             AND   trunc(sysdate) BETWEEN effective_start_date
1381                                  AND     effective_end_date
1382             -- Bug 4684198 - remove nvl on effective_end_date - col is not null
1383             AND   rownum = 1;
1384 
1385         EXCEPTION
1386             WHEN OTHERS THEN
1387                 raise PersonException;
1388         END;
1389 
1390         IF v_validated <> 'Y' then
1391                 raise PersonException;
1392         END IF;
1393 
1394         -- pick the Organization id for the Current Assignment
1395         -- where assignment type is primary type.
1396         -- it may raise no data found exception if person is not on
1397         -- current assignment
1398         SELECT organization_id
1399         INTO   v_orgid
1400         FROM   per_all_assignments_f -- Bug 4684198 - use base table not view
1401         WHERE  person_id = P_PersonId
1402         AND    trunc(sysdate) BETWEEN effective_start_date
1403                               AND     effective_end_date
1404         -- Bug 4684198 - remove nvl on effective_end_date - col is not null
1405         AND    primary_flag = 'Y'
1406     AND    assignment_type in ('E', 'C'); /* added for bug 2745823 */
1407 
1408         -- pick the Object id for the organization
1409         SELECT distinct object_id
1410         INTO   v_objid
1411         FROM   fnd_objects
1412         WHERE  obj_name = v_objname;
1413 
1414         -- get the roleid for the Responsibility of type 'Resource Authority');
1415         v_roleid := pa_security_pvt.get_menu_id(v_rolename);
1416         v_Primroleid := pa_security_pvt.get_menu_id(v_primrolename);
1417 
1418         IF (v_Primroleid is  NULL and  v_roleid is  NULL) then
1419                 raise missing_role;
1420         END IF;
1421 
1422         BEGIN
1423                 SELECT  pep.person_id,
1424       --distinct to_number(substr(fg.grantee_key,instr(fg.grantee_key,':')+1)),
1425                         pep.full_name
1426                 INTO    P_PrimaryContactId,P_PrimaryContactName
1427                 FROM   fnd_grants fg,
1428                        per_all_people_f pep, -- Bug 4684198 - use table
1429                        wf_roles wfr
1430                 WHERE  fg.object_id = v_objid
1431                 AND    fg.instance_pk1_value = TO_CHAR(v_orgid)
1432                 AND    fg.menu_id = v_Primroleid
1433                 AND    fg.instance_type = 'INSTANCE'
1434                 AND wfr.orig_system    = 'HZ_PARTY'
1435                 AND pep.party_id = wfr.orig_system_id
1436                 -- AND    'PER:' || pep.person_id = fg.grantee_key
1437                 -- AND    pep.person_id = substr(fg.grantee_key,instr(fg.grantee_key,':')+1)
1438                 AND    trunc(SYSDATE) BETWEEN trunc(fg.start_date)
1439                                       AND     trunc(NVL(fg.end_date, SYSDATE+1))
1440                 AND    trunc(sysdate) BETWEEN pep.effective_start_date
1441                                       AND     pep.effective_end_date
1442                 AND    wfr.name = fg.grantee_key; -- added for perf bug 4887312
1443             -- Bug 4684198 - remove nvl on effective_end_date - col is not null
1444 
1445                 --dbms_output.put_line(P_primarycontactid||P_primarycontactName);
1446 
1447         EXCEPTION
1448                 WHEN  NO_DATA_FOUND THEN
1449                        -- x_return_status := FND_API.G_RET_STS_ERROR;
1450                        -- x_error_message_code := 'PA_RESOURCE_NO_PRIMARY_CONTACT';
1451                        -- NULL; Commented NULL for 4537865
1452 
1453                P_PrimaryContactId := NULL ; -- 4537865
1454             P_PrimaryContactName := NULL ; -- 4537865
1455                 WHEN OTHERS THEN
1456                        -- NULL; 4537865
1457              P_PrimaryContactId := NULL ; -- 4537865
1458                         P_PrimaryContactName := NULL ; -- 4537865
1459         END;
1460         -- get the  analystid for the Person
1461         -- initialize the plsqltab value to avoid nodatafound exception
1462         -- in calling program
1463           j := 1;
1464         P_ResourceAnalystTab(1):= NULL;
1465         P_ResourceIdTab(1) := NULL;
1466         FOR i IN analystid(v_objid, v_orgid, v_roleid) LOOP
1467        -- P_ResourceIdTab(j) := to_number(substr(i.grantee_key,instr(i.grantee_key,':')+1));
1468        P_ResourceIdTab(j) := i.person_id;
1469                    IF (P_ResourceIdTab(j) is NOT NULL)  then
1470                         BEGIN
1471                              SELECT full_name
1472                              INTO   P_ResourceAnalystTab(j)
1473                              FROM   per_all_people_f -- Bug 4684198
1474                              WHERE  person_id = P_ResourceIdTab(j)
1475                              AND    trunc(sysdate) BETWEEN effective_start_date
1476                                                    AND     effective_end_date;
1477             -- Bug 4684198 - remove nvl on effective_end_date - col is not null
1478 
1479                        EXCEPTION
1480                              WHEN  NO_DATA_FOUND THEN
1481                                -- x_return_status := FND_API.G_RET_STS_ERROR;
1482                                -- x_error_message_code := 'PA_RESOURCE_NO_ANALYST';
1483                                  NULL;
1484                              WHEN OTHERS THEN
1485                                  NULL;
1486                        END;
1487 
1488 
1489                              j := j + 1;
1490                    END IF;
1491         END LOOP;
1492           -- if no rows found for the roleid,orgid,objid for a
1493           -- person then raie exception to avoid no data found in
1494           -- out paraemter plsql tables - P_ResourceIdTab.
1495         IF P_ResourceIdTab(1) IS NULL and P_PrimaryContactId is NULL  then
1496                   x_return_status := FND_API.G_RET_STS_ERROR;
1497                   x_error_message_code := 'PA_RESOURCE_NO_APPROVAL';
1498         END IF;
1499 EXCEPTION
1500 
1501 
1502         WHEN  PersonException then
1503           P_PrimaryContactId := NULL ;  --4537865
1504           P_PrimaryContactName := NULL ; --4537865
1505           x_return_status := FND_API.G_RET_STS_ERROR;
1506           x_error_message_code := 'PA_RESOURCE_INVALID_PERSON';
1507 
1508          WHEN  NO_DATA_FOUND THEN
1509 
1510           P_PrimaryContactId := NULL ;  --4537865
1511           P_PrimaryContactName := NULL ; --4537865
1512 
1513           x_return_status := FND_API.G_RET_STS_ERROR;
1514           x_error_message_code := 'PA_RESOURCE_INVALID_PERSON';
1515 
1516 
1517         WHEN OTHERS THEN  -- will also handle missing role
1518       P_PrimaryContactId := NULL ;  --4537865
1519       P_PrimaryContactName := NULL ; --4537865
1520           x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1521           --dbms_output.put_line('missing role exception');
1522           raise;
1523 
1524 end get_resource_analyst ;
1525 
1526 --
1527 --  PROCEDURE
1528 --              get_org_primary_contact_id_name
1529 --  PURPOSE
1530 --              This  procedure does the following
1531 --              If Resource Id is passed it retrives the corresponding
1532 --              Primary resoruce contact Id and Name, Manager id and Name.
1533 --
1534 --  HISTORY
1535 --  29-SEP-2000      R Iyengar
1536 
1537 PROCEDURE get_prim_contact_id_name(P_objid   IN NUMBER,
1538                                    P_orgid   IN NUMBER,
1539                                    P_Primroleid IN NUMBER,
1540                                    p_start_date IN DATE,
1541                                    x_PrimaryContactId OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1542                                    x_PrimaryContactName OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1543                                    x_return_status   OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1544                                    x_error_message_code OUT NOCOPY VARCHAR2 ) --File.Sql.39 bug 4440895
1545 IS
1546 BEGIN
1547 
1548 
1549                 -- initialize the error stack
1550                 PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_prim_contact_id_name');
1551                 -- initialize the return  status to success
1552                 x_return_status := FND_API.G_RET_STS_SUCCESS;
1553 
1554 
1555                 SELECT  distinct pep.person_id -- changes for 11.5.10 security
1556                       --  to_number(substr(fg.grantee_key,instr(fg.grantee_key,':')+1))
1557                         ,pep.full_name
1558                 INTO    x_PrimaryContactId,x_PrimaryContactName
1559                 FROM   fnd_grants fg,
1560                        per_all_people_f pep,  -- Bug 4684198 - use table
1561                        wf_roles wfr
1562                 WHERE  fg.object_id = P_objid
1563                 AND    fg.instance_pk1_value = to_char(P_orgid)
1564                 AND    fg.menu_id = P_Primroleid
1565                 AND    fg.instance_type = 'INSTANCE'
1566                 AND    fg.grantee_key   = wfr.name
1567                 AND    wfr.orig_system  = 'HZ_PARTY'
1568                 AND    pep.party_id = wfr.orig_system_id
1569                 AND    trunc(SYSDATE) BETWEEN trunc(fg.start_date)
1570                                       AND     trunc(NVL(fg.end_date, SYSDATE+1))
1571                -- AND    'PER:' || pep.person_id = fg.grantee_key --bug 2795616:perfomance
1572                 -- AND    pep.person_id = substr(fg.grantee_key,instr(fg.grantee_key,':')+1)
1573                 AND    p_start_date BETWEEN pep.effective_start_date
1574                                     AND     pep.effective_end_date
1575                 and (PEP.current_employee_flag = 'Y' or PEP.current_npw_flag = 'Y');
1576             -- Bug 4684198 - remove nvl on effective_end_date - col is not null
1577 
1578                 -- reset the error stack
1579                 PA_DEBUG.reset_err_stack;
1580 
1581         EXCEPTION
1582                 WHEN  NO_DATA_FOUND THEN
1583                    -- as discussed with Mr.Ramesh,this is not a business rule violation
1584                    --  so commented
1585                    --     x_return_status := FND_API.G_RET_STS_ERROR;
1586                    --     x_error_message_code := 'PA_RESOURCE_NO_ANALYST';
1587 
1588              x_PrimaryContactId := NULL; -- 4537865
1589                    x_PrimaryContactName := NULL ; -- 4537865
1590 
1591           --  Null; Commented NULL for 4537865
1592 
1593                 WHEN OTHERS THEN
1594            x_PrimaryContactId := NULL; -- 4537865
1595            x_PrimaryContactName := NULL ; -- 4537865
1596                    -- this is not business rule violation
1597                      -- Null; -- Commented null for 4537865
1598 
1599 
1600 END get_prim_contact_id_name ;
1601 
1602 --
1603 --  PROCEDURE
1604 --              get_manager_id_name
1605 -- this  procedure gets the Manager name and id for specified person
1606 -- and called from get_org_primary_contact
1607 PROCEDURE get_manager_id_name(P_personid           IN  NUMBER,
1608                               p_start_date         IN  DATE,
1609                               x_ManagerId          OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1610                               x_ManagerName        OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1611                               x_error_message_code OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1612                               x_return_status      OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
1613 IS
1614         BEGIN
1615                 -- initialize the error stack
1616                 PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_manager_id_name');
1617                 -- initialize the return  status to success
1618                 x_return_status := FND_API.G_RET_STS_SUCCESS;
1619 
1620                 --Modified code for future dated person
1621                 --Manager check is still as of sysdate
1622 				SELECT assn.supervisor_id,pep.full_name
1623                 INTO   x_ManagerId,x_ManagerName
1624                 FROM   per_all_assignments_f assn,per_all_people_f pep
1625                 WHERE  assn.person_id = P_personId
1626                 AND    pep.person_id = assn.supervisor_id
1627                 AND    trunc(p_start_date) BETWEEN assn.effective_start_date /*Bug 8817301 */
1628                                     AND     assn.effective_end_date
1629                 AND    trunc(sysdate) BETWEEN pep.effective_start_date
1630                                       AND     pep.effective_end_date
1631                 AND    primary_flag = 'Y'
1632 		AND    assignment_type in ('C', 'E');
1633 
1634                 -- reset the error stack
1635                 PA_DEBUG.reset_err_stack;
1636 
1637       EXCEPTION
1638         WHEN NO_DATA_FOUND THEN
1639                    -- as discussed with Mr.Ramesh,this is not a business rule violation
1640                    --  so commented
1641                    --     x_return_status := FND_API.G_RET_STS_ERROR;
1642                    --     x_error_message_code := 'PA_RESOURCE_NO_MANAGER';
1643 
1644               x_ManagerId := NULL ; -- 4537865
1645               x_ManagerName :=  NULL ; -- 4537865
1646 
1647               /*bug 3737529 - Code addition starts*/
1648                BEGIN
1649               SELECT assn.supervisor_id,pep.full_name
1650               INTO   x_ManagerId,x_ManagerName
1651               FROM   per_all_assignments_f assn,
1652                                  per_all_people_f pep
1653               WHERE  assn.person_id = P_personId
1654               AND    pep.person_id = assn.supervisor_id
1655               AND    trunc(p_start_date) BETWEEN assn.effective_start_date /*Bug 8817301 */
1656                                   AND     assn.effective_end_date
1657               AND    trunc(sysdate) BETWEEN pep.effective_start_date
1658                                     AND     pep.effective_end_date
1659               AND    primary_flag = 'Y'
1660               AND    assignment_type = 'B';
1661 
1662 
1663             EXCEPTION
1664               WHEN NO_DATA_FOUND THEN
1665                 x_ManagerId := NULL ; -- 4537865
1666                 x_ManagerName :=  NULL ; -- 4537865
1667                -- l NULL; Commented NULL for 4537865
1668             END;
1669               /*bug 3737529 - Code addition ends*/
1670 When TOO_MANY_ROWS THEN
1671 
1672  x_ManagerId := NULL ;
1673               x_ManagerName :=  NULL ;
1674 
1675 
1676                BEGIN
1677 SELECT assn.supervisor_id,pep.full_name
1678                 INTO   x_ManagerId,x_ManagerName
1679                 FROM   per_all_assignments_f assn,per_all_people_f pep
1680                 WHERE  assn.person_id = P_personId
1681                 AND    pep.person_id = assn.supervisor_id
1682                 AND    trunc(p_start_date) BETWEEN assn.effective_start_date /*Bug 8817301 */
1683                                     AND     assn.effective_end_date
1684                 AND    trunc(sysdate) BETWEEN pep.effective_start_date
1685                                       AND     pep.effective_end_date
1686                 AND    primary_flag = 'Y'
1687 		AND    assignment_type in ('C', 'E') /* added for bug 2745823 */
1688                 AND ((SELECT per_system_status
1689                       FROM per_assignment_status_types past
1690                       WHERE past.assignment_status_type_id = assn.assignment_status_type_id) IN ('ACTIVE_ASSIGN','ACTIVE_CWK')); --Bug#8879958
1691 
1692             EXCEPTION
1693               WHEN NO_DATA_FOUND THEN
1694                 x_ManagerId := NULL ;
1695                 x_ManagerName :=  NULL ;
1696 
1697             END;
1698 
1699 
1700 
1701     WHEN OTHERS THEN
1702      -- this is not a business rule violation
1703      x_ManagerId := NULL ; -- 4537865
1704      x_ManagerName :=  NULL ; -- 4537865
1705     -- Null; Commented NULL for 4537865
1706 
1707 END get_manager_id_name;
1708 
1709 
1710 
1711 
1712 --
1713 --  PROCEDURE
1714 --              get_org_id
1715 -- This procedure is called from get_org_primary_contact
1716 PROCEDURE get_org_id(P_personid            IN  NUMBER,
1717                      p_start_date          IN  DATE,
1718                      x_orgid               OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1719                      x_error_message_code  OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1720                      x_return_status       OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
1721 IS
1722 BEGIN
1723 
1724         -- initialize the error stack
1725         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_org_id');
1726         -- initialize the return  status to success
1727         x_return_status := FND_API.G_RET_STS_SUCCESS;
1728 
1729         -- pick the Organization id for the Current Assignment
1730         -- where assignment type is primary type.
1731         -- may raise exception if the person is not on current assnment
1732         SELECT organization_id
1733         INTO   x_orgid
1734         FROM   per_all_assignments_f
1735         WHERE  person_id = P_personId
1736         AND    trunc(p_start_date)  BETWEEN effective_start_date --bug 9403051
1737                              AND     effective_end_date
1738         AND    primary_flag = 'Y'
1739     AND    assignment_type in ('E', 'C'); /* added for bug 2745823 */
1740 
1741         -- reset the error stack
1742         PA_DEBUG.reset_err_stack;
1743 
1744 EXCEPTION
1745                 WHEN OTHERS THEN
1746                    -- set the exception message and stack
1747                  --  FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.get_org_id'
1748                  --                          ,PA_DEBUG.g_err_stack);
1749                  --  x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1750                   -- raise;
1751                  -- null; 4537865
1752          x_orgid   := NULL ;
1753 
1754 END get_org_id;
1755 
1756 
1757 --
1758 --  PROCEDURE
1759 --              get_person_id
1760 -- This procedure is called from get_org_primary_contact
1761 PROCEDURE get_person_id(P_resourceid          IN  NUMBER,
1762                         x_personid            OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1763                         x_error_message_code  OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1764                         x_return_status       OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
1765 
1766 
1767 IS
1768         PersonException         EXCEPTION;
1769         v_validated             VARCHAR2(1);
1770 
1771 BEGIN
1772 
1773         -- initialize the error stack
1774         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_person_id');
1775         -- initialize the return  status to success
1776         x_return_status := FND_API.G_RET_STS_SUCCESS;
1777 
1778         IF P_resourceid is NOT NULL  then
1779                 -- may raise too many rows exception
1780                 SELECT Person_id
1781                 INTO   x_personId
1782                 FROM   pa_resource_txn_attributes
1783                 WHERE  resource_id = P_ResourceId;
1784 
1785                 IF x_PersonId is NULL then
1786                         raise PersonException;
1787                 END IF;
1788 
1789 
1790              /* The code below is commented out to accomodate
1791                 future dated employees Bug 1944726
1792               */
1793              /*
1794                   -- Validate the PersonId
1795                 BEGIN
1796 
1797                     SELECT 'Y'
1798                     INTO  v_validated
1799                     FROM  per_people_f
1800                     WHERE person_id = x_personId
1801                     AND   trunc(sysdate) BETWEEN effective_start_date
1802                     AND   NVL(effective_end_date,sysdate + 1)
1803                     AND   rownum = 1;
1804 
1805                 EXCEPTION
1806                     WHEN OTHERS THEN
1807                         raise PersonException;
1808                 END;
1809 
1810                 IF v_validated <> 'Y' then
1811                     raise PersonException;
1812                 END IF;
1813 
1814              */
1815 
1816         END IF;
1817 
1818         -- reset the error stack
1819         PA_DEBUG.reset_err_stack;
1820 
1821 
1822 EXCEPTION
1823         WHEN  NO_DATA_FOUND THEN
1824         x_PersonId := NULL ; --4537865
1825                 x_error_message_code := 'PA_RESOURCE_INVALID_RESOURCE';
1826                 x_return_status := FND_API.G_RET_STS_ERROR;
1827 
1828         WHEN PersonException then
1829         x_PersonId := NULL ; -- 4537865
1830                 x_error_message_code := 'PA_RESOURCE_INVALID_PERSON';
1831                 x_return_status := FND_API.G_RET_STS_ERROR;
1832 
1833 
1834         WHEN OTHERS THEN
1835                 -- set the exception message and stack
1836         x_PersonId := NULL ; -- 4537865
1837                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.get_org_id'
1838                                         ,PA_DEBUG.g_err_stack);
1839                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
1840                 raise;
1841 
1842 END get_person_id;
1843 
1844 
1845 PROCEDURE get_object_id(P_objname            IN VARCHAR2,
1846                         x_objid              OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1847                         x_error_message_code OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1848                         x_return_status      OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
1849 IS
1850 BEGIN
1851 
1852         -- initialize the error stack
1853         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_object_id');
1854         -- initialize the return  status to success
1855         x_return_status := FND_API.G_RET_STS_SUCCESS;
1856 
1857 
1858        -- pick the Object id for the organization (seeded data)
1859         SELECT distinct object_id
1860         INTO   x_objid
1861         FROM   fnd_objects
1862         WHERE  obj_name = P_objname;
1863 
1864 
1865         -- reset the error stack
1866         PA_DEBUG.reset_err_stack;
1867 
1868 EXCEPTION
1869         WHEN OTHERS THEN
1870         x_objid := NULL ; -- 4537865
1871                     -- 4537865  Null;
1872 
1873 
1874 END get_object_id;
1875 
1876 
1877 --
1878 --  PROCEDURE
1879 --              get_org_primary_contact
1880 --  PURPOSE
1881 --              This  procedure does the following
1882 --              If Resource Id is passed it retrives the corresponding
1883 --              resource primary contact Id , Name,Managerid and manager name.
1884 --  HISTORY
1885 --
1886 --  29-SEP-2000      R Iyengar   created
1887 --  05-SEP-2001      Vijay Ranganathan  Added p_assignment_id parameter
1888 PROCEDURE get_org_primary_contact
1889                           (p_ResourceId           IN  NUMBER,
1890                            p_assignment_id        IN  NUMBER,
1891                            x_PrimaryContactId     OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1892                            x_PrimaryContactName   OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1893                            x_ManagerId            OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1894                            x_ManagerName          OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1895                            x_return_Status        OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
1896                            x_msg_count            OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
1897                            x_msg_data             OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
1898                            ) is
1899 
1900         v_personId              NUMBER;
1901         v_numrows               NUMBER;
1902         v_orgid                 per_all_assignments_f.organization_id%TYPE;
1903         v_objid                 fnd_grants.object_id%TYPE;
1904         --v_resid                 fnd_grants.grantee_key%TYPE;
1905         v_objname               VARCHAR2(25) := 'ORGANIZATION';
1906         v_primrolename          VARCHAR2(30) := 'PA_PRM_RES_PRMRY_CONTACT';
1907         v_primroleid            fnd_grants.menu_id%TYPE;
1908         v_error_message_code    fnd_new_messages.message_name%TYPE;
1909         v_return_status         VARCHAR2(1);
1910         v_msg_data              VARCHAR2(2000);
1911         v_msg_count             NUMBER;
1912         v_msg_index_out         NUMBER;
1913         l_start_date            DATE;
1914 
1915 BEGIN
1916        -- initialize the error stack
1917        PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_org_primary_contact');
1918 
1919        -- initialize the return status to success
1920        x_return_status := FND_API.G_RET_STS_SUCCESS;
1921 
1922        IF p_assignment_id IS NULL THEN
1923           l_start_date := sysdate;
1924        ELSE
1925           --Get the assignment start date
1926            BEGIN
1927               SELECT start_date
1928               INTO   l_start_date
1929               FROM   pa_project_assignments
1930               WHERE  assignment_id = p_assignment_id
1931               ;
1932            EXCEPTION
1933               WHEN OTHERS THEN
1934                 l_start_date := sysdate;
1935            END;
1936        END IF;
1937 
1938        -- Added for bug 7623859
1939        IF (sysdate > l_start_date) THEN
1940          l_start_date := sysdate;
1941        END IF;
1942 
1943        -- get the person id for resource id
1944         get_person_id(P_ResourceId
1945                      ,v_personid
1946                      ,v_error_message_code
1947                      ,v_return_status);
1948         --check for return status if error found then add it to stack
1949         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
1950            PA_UTILS.add_message(p_app_short_name => 'PA',
1951                                 p_msg_name => v_error_message_code);
1952         END IF;
1953 
1954        -- get the organization id for the name for the person
1955        get_org_id(v_personid
1956                  ,l_start_date
1957                  ,v_orgid
1958                  ,v_error_message_code
1959                  ,v_return_status);
1960         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
1961            PA_UTILS.add_message(p_app_short_name => 'PA',
1962                                 p_msg_name       => v_error_message_code);
1963         END IF;
1964 
1965 
1966      -- get object id for the object name
1967        get_object_id(v_objname
1968                     ,v_objid
1969                     ,v_error_message_code
1970                     ,v_return_status);
1971 
1972 
1973         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
1974            PA_UTILS.add_message(p_app_short_name => 'PA',
1975                                 p_msg_name => v_error_message_code);
1976         END IF;
1977 
1978 
1979        -- get the roleid for the Responsibility of type 'Primary Resource Contact'
1980        v_Primroleid := pa_security_pvt.get_menu_id(v_primrolename);
1981       -- get primary contact name and id
1982       get_prim_contact_id_name(v_objid
1983                               ,v_orgid
1984                               ,v_Primroleid
1985                               ,l_start_date
1986                               ,x_PrimaryContactId
1987                               ,x_PrimaryContactName
1988                               ,v_return_status
1989                               ,v_error_message_code );
1990 
1991         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
1992            PA_UTILS.add_message(p_app_short_name => 'PA',
1993                                 p_msg_name => v_error_message_code);
1994         END IF;
1995 
1996 
1997        -- get manager name and id
1998        get_manager_id_name(v_personid
1999                           ,l_start_date
2000                           ,x_ManagerId
2001                           ,x_ManagerName
2002                           ,v_error_message_code
2003                           ,v_return_status);
2004         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
2005            PA_UTILS.add_message(p_app_short_name => 'PA',
2006                                 p_msg_name => v_error_message_code);
2007         END IF;
2008 
2009         -- as discussed with Ms.Angela if both manager and primary contact  is null
2010         -- then  pass the error messages.
2011         IF (x_ManagerId is NULL and x_primarycontactid is NULL) then
2012                     PA_UTILS.add_message(p_app_short_name => 'PA',
2013                                 p_msg_name => 'PA_RESOURCE_NO_APPROVAL');
2014                     x_return_status := FND_API.G_RET_STS_ERROR;
2015 
2016         END IF;
2017 
2018       v_msg_count := FND_MSG_PUB.count_msg;
2019 
2020       -- if num of message is one then pass it to out parameter x_msg_data
2021       IF v_msg_count = 1 and (x_ManagerId is NULL and x_primarycontactid is NULL) then
2022           PA_INTERFACE_UTILS_PUB.get_messages(
2023                         p_encoded  => FND_API.G_TRUE
2024                        ,p_msg_index => 1
2025                        ,p_msg_count => v_msg_count
2026                        ,p_data      => v_msg_data
2027                        ,p_msg_index_out => v_msg_index_out);
2028           x_msg_data := v_msg_data;
2029           x_msg_count := v_msg_count;
2030       ELSE
2031           x_msg_count := v_msg_count;
2032       END IF;
2033 
2034         -- reset the error stack
2035         PA_DEBUG.reset_err_stack;
2036 
2037 
2038 EXCEPTION
2039 
2040         WHEN OTHERS THEN
2041 
2042         -- Reset OUT params : 4537865
2043         x_PrimaryContactId := NULL ;
2044         x_PrimaryContactName  :=  NULL ;
2045                 x_ManagerId  := NULL;
2046                 x_ManagerName      := NULL ;
2047                 x_return_Status    := NULL ;
2048 
2049                 -- set the exception message and stack
2050                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.get_org_primary_contact'
2051                                         ,PA_DEBUG.g_err_stack);
2052                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2053                 --      dbms_output.put_line('missing');
2054                 raise;
2055 
2056 
2057 end get_org_primary_contact ;
2058 
2059 FUNCTION get_resource_id(P_Person_Id IN NUMBER)
2060 RETURN NUMBER
2061 IS
2062 l_resource_id NUMBER;
2063 BEGIN
2064 
2065    SELECT resource_id
2066    INTO l_resource_id
2067    FROM pa_resource_txn_attributes
2068    WHERE person_id = p_person_id;
2069 
2070    RETURN l_resource_id;
2071 EXCEPTION
2072   WHEN OTHERS THEN
2073        RETURN -999;
2074 END get_resource_id;
2075 
2076 -- Changes for BUG: 1660614 are as follows.
2077 --      Added parameter p_date in DATE
2078 --      The above parameter p_date stands for period_end_date
2079 --      and is used instead of sysdate used before
2080 -- Changes for Organization Utilization performance improvements
2081 -- Logic uses PA_RESOURCES_DENORM table instead of PER_ASSIGNMENTS_F
2082 FUNCTION Get_People_Assigned(p_org_id in pa_resources_denorm.resource_organization_id%TYPE,
2083                              p_date in DATE,
2084 			     p_emp_type IN VARCHAR DEFAULT 'EMP') RETURN NUMBER --Added p_emp_type for bug 5680366
2085 IS
2086  l_count NUMBER;
2087 BEGIN
2088 /* Commented for bug 5680366
2089   select count(*) into l_count
2090   from   pa_resources_denorm
2091   where  resource_organization_id   = p_org_id
2092   and    p_date between resource_effective_start_date and resource_effective_end_date;
2093 */
2094 
2095 IF p_emp_type = 'EMP' THEN -- Added IF for 5680366
2096   select count(*) into l_count
2097   from   pa_resources_denorm
2098   where  resource_organization_id   = p_org_id
2099   and    p_date between resource_effective_start_date and resource_effective_end_date
2100   AND    RESOURCE_PERSON_TYPE = 'EMP';
2101 ELSIF p_emp_type = 'CWK' THEN -- Added ELSE for 5680366
2102   select count(*) into l_count
2103   from   pa_resources_denorm
2104   where  resource_organization_id   = p_org_id
2105   and    p_date between resource_effective_start_date and resource_effective_end_date
2106   AND    RESOURCE_PERSON_TYPE = 'CWK';
2107 ELSE ---Same as earlier
2108   select count(*) into l_count
2109   from   pa_resources_denorm
2110   where  resource_organization_id   = p_org_id
2111   and    p_date between resource_effective_start_date and resource_effective_end_date;
2112 END IF;
2113 
2114   --dbms_output.put_line('Count in Get_People_Assigned =  '|| to_char(l_count));
2115   return l_count;
2116 
2117 EXCEPTION
2118  WHEN NO_DATA_FOUND THEN
2119    return 0;
2120  WHEN OTHERS THEN
2121    return -999;
2122 END Get_People_Assigned;
2123 
2124 --
2125 --  FUNCTION
2126 --              Get_Resource_Headcount
2127 --  PURPOSE
2128 --              This  function gets the resource head count for a given
2129 --              organization, category, period type, period name, Global
2130 --              week end date and year.
2131 --
2132 --  HISTORY     Changes for BUG: 1660614
2133 --              Added the following new parameters:
2134 --              p_category : This could be one of the following.
2135 --                         1. SUBORG_EMP - Includes all subordinate excluding the direct reports
2136 --                         2. DIRECT_EMP - Includes all the direct reports
2137 --                         3. TOTAL_EMP - Includes all subordinates
2138 --              p_period_type: Possible values are GL - gl period, GE - global expenditure
2139 --                             week, PA - pa period, QR - quarter, YR - year
2140 --              p_period_name: Values only for GL and PA periods, Quarter number for QR
2141 --              p_end_date: Only for global expenditure week GE
2142 --              p_year : For YR and QR types - pass the year
2143 --              Changes for Performance enhancement of Organization Utilization page
2144 --              For GL, PA, QR and YR period types the where clause
2145 --              uses base tables instead of pa_rep_periods_dates_v
2146 FUNCTION Get_Resource_Headcount(p_org_id IN NUMBER,
2147                 p_category IN VARCHAR2,
2148                                 p_period_type IN VARCHAR2,
2149                                 p_period_name IN VARCHAR2,
2150                                 p_end_date in DATE,
2151                                 p_year in NUMBER) RETURN NUMBER
2152     IS
2153     --MOAC Changes : Bug 4363092: Get the value of org from PA_MOAC_UTILS.GET_CURRENT_ORG_ID
2154 /*      CURSOR c_suborg(p_org_id in pa_resources_denorm.resource_organization_id%TYPE) IS
2155         select org.child_organization_id c_org
2156         from   pa_org_hierarchy_denorm org,
2157                pa_implementations imp
2158         where  org.parent_organization_id         = p_org_id
2159         and    org.parent_level - org.child_level = 1
2160         and    org.pa_org_use_type                = 'REPORTING'
2161         and    org.org_hierarchy_version_id       = imp.org_structure_version_id
2162         and    nvl(org.org_id,nvl(to_number(decode(substr(userenv('client_info'),1,1),' ',null,
2163                substr(userenv('client_info'),1,10))), -99)) =
2164                  nvl(to_number(decode(substr(userenv('client_info'),1,1),' ',null,substr(userenv('client_info'),1,10))),-99)
2165         order by org.child_organization_id; */
2166         CURSOR c_suborg(p_org_id in pa_resources_denorm.resource_organization_id%TYPE) IS
2167         select org.child_organization_id c_org
2168         from   pa_org_hierarchy_denorm org,
2169                pa_implementations imp
2170         where  org.parent_organization_id         = p_org_id
2171         and    org.parent_level - org.child_level = 1
2172         and    org.pa_org_use_type                = 'REPORTING'
2173         and    org.org_hierarchy_version_id       = imp.org_structure_version_id
2174         and    nvl(org.org_id,NVL(PA_MOAC_UTILS.GET_CURRENT_ORG_ID,-99)) = NVL(PA_MOAC_UTILS.GET_CURRENT_ORG_ID,-99)
2175         order by org.child_organization_id;
2176 
2177         l_count  NUMBER := 0;
2178         l_num    NUMBER := 0 ;
2179 
2180         l_org_sub_count       PA_PLSQL_DATATYPES.NumTabTyp;
2181         l_org_direct_count    PA_PLSQL_DATATYPES.NumTabTyp;
2182 
2183         l_date                DATE;
2184 
2185 BEGIN
2186 
2187         IF (p_period_type = 'GL') THEN
2188 
2189       select glp.end_date into l_date
2190           from   gl_periods glp,
2191                  gl_sets_of_books glsob,
2192                  pa_implementations pai
2193           where  pai.set_of_books_id         = glsob.set_of_books_id
2194           and    glsob.period_set_name       = glp.period_set_name
2195           and    glsob.accounted_period_type = glp.period_type
2196           and    glp.period_name             = p_period_name;
2197 
2198         ELSIF (p_period_type = 'PA') THEN
2199               /* code commented for  Bug 2634995
2200                        select pap.pa_end_date into l_date
2201                        from   pa_periods_v pap,
2202                               pa_implementations pai
2203                        where  pap.period_name     = p_period_name
2204                        and    pai.set_of_books_id = pap.set_of_books_id;
2205               */
2206 
2207             /* Select from pa_periods_v is replaced by view definition for Perfomance
2208                Bug 2634995        */
2209             SELECT pap.end_date
2210             INTO   l_date
2211             FROM   PA_PERIODS PAP,
2212                    GL_PERIOD_STATUSES GLP,
2213                    PA_IMPLEMENTATIONS PAIMP,
2214                    PA_LOOKUPS PAL
2215             WHERE PAP.period_name  = p_period_name
2216             AND   PAP.GL_PERIOD_NAME = GLP.PERIOD_NAME
2217             AND   GLP.SET_OF_BOOKS_ID = PAIMP.SET_OF_BOOKS_ID
2218             AND   GLP.APPLICATION_ID = Pa_Period_Process_Pkg.Application_id
2219             AND   GLP.ADJUSTMENT_PERIOD_FLAG = 'N'
2220             AND   GLP.CLOSING_STATUS = PAL.LOOKUP_CODE /*Added for bug 5484203*/
2221             AND   PAL.LOOKUP_TYPE = 'CLOSING STATUS';
2222 
2223 
2224         ELSIF (p_period_type = 'YR') THEN
2225 
2226           select max(glp.end_date)
2227           into l_date
2228           from   gl_periods glp,
2229                  gl_sets_of_books glsob,
2230                  pa_implementations pai
2231           where  pai.set_of_books_id         = glsob.set_of_books_id
2232           and    glsob.period_set_name       = glp.period_set_name
2233           and    glsob.accounted_period_type = glp.period_type
2234           and    glp.period_year             = p_year;
2235 
2236         ELSIF (p_period_type = 'QR') THEN
2237 
2238           select max(glp.end_date)
2239           into l_date
2240           from   gl_periods glp,
2241                  gl_sets_of_books glsob,
2242                  pa_implementations pai
2243           where  pai.set_of_books_id         = glsob.set_of_books_id
2244           and    glsob.period_set_name       = glp.period_set_name
2245           and    glsob.accounted_period_type = glp.period_type
2246           and    glp.quarter_num             = to_number(p_period_name)
2247           and    glp.period_year             = p_year;
2248 
2249         ELSE
2250           l_date := p_end_date;
2251         END IF;
2252 	/*
2253 		Bug5680366	1.Added conditions for 'SUBORG_OTHERS' , 'DIRECT_OTHERS' and 'TOTALS_OTHERS' based on
2254 				'SUBORG_EMP' , 'DIRECT_EMP' and 'TOTALS_EMP' resp.
2255 	`			2.Added 'EMP' param for EMPs and 'CWK' param for OTHERs  in Get_People_Assigned
2256 	*/
2257         IF (p_category = 'SUBORG_EMP') THEN
2258           IF  not l_org_sub_count.exists(p_org_id) THEN
2259             FOR eRec IN c_suborg(p_org_id) LOOP
2260               --  l_num := Get_People_Assigned(eRec.c_org,l_date);
2261                 l_num := get_resource_headcount(eRec.c_org,'TOTALS_EMP',p_period_type,p_period_name,l_date,p_year);
2262                 l_count := l_count + l_num ;
2263              END LOOP;
2264              l_org_sub_count(p_org_id) := l_count;
2265            ELSE
2266              l_count := l_org_sub_count(p_org_id);
2267            END IF;
2268         ELSIF (p_category = 'DIRECT_EMP') THEN
2269            IF  not l_org_direct_count.exists(p_org_id) THEN
2270                l_count := Get_People_Assigned(p_org_id,l_date);
2271                l_org_direct_count(p_org_id) := l_count;
2272            ELSE
2273                l_count := l_org_direct_count(p_org_id);
2274            END IF;
2275         ELSIF (p_category = 'TOTALS_EMP') THEN
2276            IF  not l_org_sub_count.exists(p_org_id) and not l_org_direct_count.exists(p_org_id) THEN
2277                 l_count := Get_People_Assigned(p_org_id,l_date) + get_resource_headcount(p_org_id,'SUBORG_EMP',p_period_type,p_period_name,p_end_date,p_year);
2278            ELSE
2279                 l_count := l_org_sub_count(p_org_id) + l_org_direct_count(p_org_id);
2280            END IF;
2281 	ELSIF (p_category = 'SUBORG_OTHERS') THEN --Added for bug 5680366
2282           IF  not l_org_sub_count.exists(p_org_id) THEN
2283             FOR eRec IN c_suborg(p_org_id) LOOP
2284               --  l_num := Get_People_Assigned(eRec.c_org,l_date);
2285                 l_num := get_resource_headcount(eRec.c_org,'TOTALS_OTHERS',p_period_type,p_period_name,l_date,p_year);
2286                 l_count := l_count + l_num ;
2287              END LOOP;
2288              l_org_sub_count(p_org_id) := l_count;
2289            ELSE
2290              l_count := l_org_sub_count(p_org_id);
2291            END IF;
2292         ELSIF (p_category = 'DIRECT_OTHERS') THEN --Added for bug 5680366
2293            IF  not l_org_direct_count.exists(p_org_id) THEN
2294                l_count := Get_People_Assigned(p_org_id,l_date,'CWK');
2295                l_org_direct_count(p_org_id) := l_count;
2296            ELSE
2297                l_count := l_org_direct_count(p_org_id);
2298            END IF;
2299         ELSIF (p_category = 'TOTALS_OTHERS') THEN --Added for bug 5680366
2300            IF  not l_org_sub_count.exists(p_org_id) and not l_org_direct_count.exists(p_org_id) THEN
2301                 l_count := Get_People_Assigned(p_org_id,l_date,'CWK') + get_resource_headcount(p_org_id,'SUBORG_OTHERS',p_period_type,p_period_name,p_end_date,p_year);
2302            ELSE
2303                 l_count := l_org_sub_count(p_org_id) + l_org_direct_count(p_org_id);
2304            END IF;
2305         END IF;
2306         return l_count;
2307 EXCEPTION
2308    WHEN NO_DATA_FOUND THEN
2309         --dbms_output.put_line('No Data Found');
2310         return 10;
2311    WHEN OTHERS THEN
2312         return -999;
2313 END Get_Resource_Headcount;
2314 
2315 /* --------------------------------------------------------------------
2316 --  FUNCTION
2317 --              Get_Period_Date
2318 --  PURPOSE
2319 --              This  function returns the period date for the following
2320 --              types of periods:
2321 --                GL - gl period
2322 --                GE - global expenditure week
2323 --                PA - pa period
2324 --                QR - quarter
2325 --                YR - year
2326 --  ARGUMENTS
2327 --
2328 --              p_period_name: Values only for GL and PA periods, Quarter
2329 --                             number for QR
2330 --              p_end_date:    Only for global expenditure week GE
2331 --              p_year :       For YR and QR types - pass the year
2332  -------------------------------------------------------------------- */
2333 
2334 PROCEDURE Set_Period_Date(p_period_type IN VARCHAR2,
2335                           p_period_name IN VARCHAR2,
2336                           p_end_date    IN DATE,
2337                           p_year        IN NUMBER)
2338 IS
2339 
2340   l_date                DATE;
2341 
2342 BEGIN
2343 
2344         IF (p_period_type = 'GL') THEN
2345 
2346       select glp.start_date into l_date
2347           from   gl_periods glp,
2348                  gl_sets_of_books glsob,
2349                  pa_implementations pai
2350           where  pai.set_of_books_id         = glsob.set_of_books_id
2351           and    glsob.period_set_name       = glp.period_set_name
2352           and    glsob.accounted_period_type = glp.period_type
2353           and    glp.period_name             = p_period_name;
2354 
2355         ELSIF (p_period_type = 'PA') THEN
2356 
2357           /* code commented for  Bug 2634995
2358            select pap.pa_start_date into l_date
2359           from   pa_periods_v pap,
2360                  pa_implementations pai
2361           where  pap.period_name     = p_period_name
2362           and    pai.set_of_books_id = pap.set_of_books_id;
2363           */
2364 
2365           /* Select from pa_periods_v is replaced by view definition for Perfomance
2366              Bug 2634995        */
2367 
2368             SELECT pap.start_date
2369             INTO   l_date
2370             FROM   PA_PERIODS PAP,
2371                    GL_PERIOD_STATUSES GLP,
2372                    PA_IMPLEMENTATIONS PAIMP,
2373                    PA_LOOKUPS PAL
2374             WHERE PAP.period_name  = p_period_name
2375             AND   PAP.GL_PERIOD_NAME = GLP.PERIOD_NAME
2376             AND   GLP.SET_OF_BOOKS_ID = PAIMP.SET_OF_BOOKS_ID
2377             AND   GLP.APPLICATION_ID = Pa_Period_Process_Pkg.Application_id
2378             AND   GLP.ADJUSTMENT_PERIOD_FLAG = 'N'
2379             AND   PAL.LOOKUP_TYPE = 'CLOSING STATUS';
2380 
2381         ELSIF (p_period_type = 'YR') THEN
2382 
2383           select min(glp.start_date)
2384           into l_date
2385           from   gl_periods glp,
2386                  gl_sets_of_books glsob,
2387                  pa_implementations pai
2388           where  pai.set_of_books_id         = glsob.set_of_books_id
2389           and    glsob.period_set_name       = glp.period_set_name
2390           and    glsob.accounted_period_type = glp.period_type
2391           and    glp.period_year             = p_year;
2392 
2393         ELSIF (p_period_type = 'QR') THEN
2394 
2395           select min(glp.start_date)
2396           into l_date
2397           from   gl_periods glp,
2398                  gl_sets_of_books glsob,
2399                  pa_implementations pai
2400           where  pai.set_of_books_id         = glsob.set_of_books_id
2401           and    glsob.period_set_name       = glp.period_set_name
2402           and    glsob.accounted_period_type = glp.period_type
2403           and    glp.quarter_num             = to_number(p_period_name)
2404           and    glp.period_year             = p_year;
2405 
2406         ELSE
2407           l_date := p_end_date - 6;
2408         END IF;
2409 
2410         PA_RESOURCE_UTILS.G_PERIOD_DATE := l_date;
2411 EXCEPTION
2412    WHEN NO_DATA_FOUND THEN
2413         PA_RESOURCE_UTILS.G_PERIOD_DATE := sysdate - 50 * 365;
2414    WHEN OTHERS THEN
2415         PA_RESOURCE_UTILS.G_PERIOD_DATE := sysdate - 50 * 365;
2416 END Set_Period_Date;
2417 
2418 FUNCTION get_resource_manager_id(p_user_id IN NUMBER) RETURN NUMBER IS
2419    l_root_manager_id NUMBER;
2420 BEGIN
2421    SELECT employee_id
2422    INTO l_root_manager_id
2423    FROM  fnd_user
2424    WHERE user_id = p_user_id;
2425    RETURN l_root_manager_id;
2426 EXCEPTION
2427  WHEN NO_DATA_FOUND THEN
2428    return 0;
2429  WHEN OTHERS THEN
2430    return -999;
2431 END get_resource_manager_id;
2432 
2433 --  PROCEDURE
2434 --              get_resource_capacity
2435 --  PURPOSE
2436 --              This function returns the capacity hours for a resource
2437 --              for the given week. If capacity = 0 it returns 1
2438 --  HISTORY
2439 --  14-MAR-2001 virangan created
2440 --  27-APR-2001 virangan modified code to return 1 if capacity = 0
2441 --  29-APR-2001 virangan modified assigned hours to be from res_asgn
2442 --                       table instead of proj_asgn
2443 --  07-MAY-2001 virangan  Removed group by clause for performance
2444 --                        Bug 1767793
2445 --  21-MAY-2001 virangan  Removed join to row label table
2446 --
2447 
2448 FUNCTION get_resource_capacity(res_id IN NUMBER, week_start_date IN DATE)
2449                                RETURN NUMBER
2450   IS
2451      capacity NUMBER;
2452 
2453 BEGIN
2454 
2455   BEGIN
2456 
2457      SELECT sum(capacity_quantity)
2458      INTO   capacity
2459      FROM   pa_forecast_items
2460      WHERE  resource_id      = res_id
2461      AND    delete_flag      = 'N'
2462      AND    forecast_item_type = 'U'
2463      AND    item_date  between week_start_date
2464                        and     week_start_date + 6;
2465   EXCEPTION
2466         WHEN NO_DATA_FOUND THEN
2467              capacity := 0;
2468   END;
2469 
2470   --The following logic is used because resource capacity
2471   --is used in denomonator in Staffing Home page
2472   IF ( capacity = 0) then
2473       RETURN 1;
2474   ELSE
2475       RETURN  capacity;
2476   END IF;
2477 
2478 END get_resource_capacity;
2479 
2480 
2481 --  PROCEDURE
2482 --              Get_Current_Project_NameNumber
2483 --  PURPOSE
2484 --              This function has been created for CURRENT_PROJECT_NAME_NUMBER column
2485 --              of pa_resource_availability_v. This will return the project namd and
2486 --              number in the format: project_name(project_number).
2487 --
2488 --  HISTORY
2489 --  09-APR-2001 snam  Created
2490 FUNCTION Get_Current_Project_NameNumber(p_resource_id IN NUMBER)
2491 RETURN VARCHAR2
2492 IS
2493   l_proj_name_number varchar2(65);
2494   l_project_id NUMBER;
2495 BEGIN
2496   -- reset current_project_id before set it up again
2497   PA_RESOURCE_UTILS.G_CURRENT_PROJECT_ID := NULL;
2498 
2499 -- 4778041 : For performance , removed join of pa_resources_denorm
2500   SELECT proj.name || '(' || proj.segment1 || ')',
2501          proj.project_id
2502     INTO l_proj_name_number,
2503          l_project_id
2504     FROM --pa_resources_denorm res,
2505          pa_project_assignments asgmt,
2506          pa_projects_all proj,
2507          pa_project_statuses ps
2508    WHERE --trunc(sysdate) between trunc(res.resource_effective_start_date)
2509          --               and trunc(res.resource_effective_end_date)
2510          --AND  res.resource_id = asgmt.resource_id
2511          --AND  res.resource_id = p_resource_id
2512 	      asgmt.resource_id = p_resource_id
2513          AND  trunc(sysdate) BETWEEN trunc(asgmt.start_date) and trunc(asgmt.end_date)
2514          AND  asgmt.project_id = proj.project_id
2515          AND  asgmt.status_code  = ps.project_status_code
2516          AND  ps.project_system_status_code = 'STAFFED_ASGMT_CONF'
2517          AND  rownum=1;
2518 
2519  -- set current project_id to the global variable so that we can get it from
2520  -- the procedure 'Get_Current_Project_Id'
2521  G_CURRENT_PROJECT_ID := l_project_id;
2522 
2523  RETURN l_proj_name_number;
2524 
2525  EXCEPTION
2526    WHEN NO_DATA_FOUND THEN
2527      RETURN null;
2528    WHEN OTHERS THEN
2529      RETURN null;
2530 END Get_Current_Project_NameNumber;
2531 
2532 --  PROCEDURE
2533 --              Get_Current_Project_Id
2534 --  PURPOSE
2535 --              This function has been created for CURRENT_PROJECT_ID column
2536 --              of pa_resource_availability_v. This procedure should be called after
2537 --              calling 'Get_Current_Project_NameNumber'.
2538 --
2539 --  HISTORY
2540 --  09-APR-2001 snam  Created
2541 FUNCTION Get_Current_Project_Id(p_resource_id IN NUMBER)
2542 RETURN NUMBER
2543 IS
2544 BEGIN
2545   return PA_RESOURCE_UTILS.G_CURRENT_PROJECT_ID;
2546 
2547 END  Get_Current_Project_Id;
2548 
2549 --  PROCEDURE
2550 --              Get_Person_name
2551 --  PURPOSE
2552 --              This procedure returns the persons name for
2553 --              a given person_id
2554 --
2555 --  HISTORY
2556 --              10-MAY-2001  created  virangan
2557 --
2558 PROCEDURE get_person_name (     p_person_id           IN  NUMBER,
2559                                 x_person_name         OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2560                                 x_return_status       OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
2561 IS
2562 BEGIN
2563 
2564         -- initialize the error stack
2565         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_person_name');
2566         -- initialize the return  status to success
2567         x_return_status := FND_API.G_RET_STS_SUCCESS;
2568 
2569         IF p_person_id IS NOT NULL  then
2570 
2571 /* changed the select statement to be based on per_all_people_f and added
2572 the sysdate condition for bug 2983491 */
2573 
2574                 SELECT full_name
2575                 INTO   x_person_name
2576                 FROM   per_all_people_f
2577                 WHERE  person_id   =  p_person_id
2578         AND    EFFECTIVE_START_DATE = (SELECT MIN(EFFECTIVE_START_DATE)  FROM   per_all_people_f
2579                                                 WHERE  person_id   =  p_person_id
2580                                         and trunc(EFFECTIVE_END_DATE) >= trunc(sysdate));
2581 
2582                 --AND    TRUNC(SYSDATE) BETWEEN EFFECTIVE_START_DATE AND EFFECTIVE_END_DATE;
2583                 --Bug 3877472 The AND condition in where clause is changed so as to include future dated employees also.
2584         ELSE
2585                x_person_name := null;
2586         END IF;
2587 
2588         -- reset the error stack
2589         PA_DEBUG.reset_err_stack;
2590 
2591 EXCEPTION
2592         WHEN  NO_DATA_FOUND THEN
2593                 x_person_name := null;
2594                 x_return_status := FND_API.G_RET_STS_ERROR;
2595 
2596         WHEN OTHERS THEN
2597 
2598         -- RESET OUT PARAM 4537865
2599         x_person_name := null;
2600 
2601                 -- set the exception message and stack
2602                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.get_person_name'
2603                                         ,PA_DEBUG.g_err_stack);
2604                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2605                 raise;
2606 
2607 END get_person_name;
2608 
2609 --  PROCEDURE
2610 --              Get_Location_Details
2611 --  PURPOSE
2612 --              This procedure returns  location details for
2613 --              given location id
2614 --
2615 --  HISTORY
2616 --              10-MAY-2001  created  virangan
2617 --
2618 PROCEDURE get_location_details (p_location_id         IN  NUMBER,
2619                                 x_address_line_1      OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2620                                 x_address_line_2      OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2621                                 x_address_line_3      OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2622                                 x_town_or_city        OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2623                                 x_postal_code         OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2624                                 x_country             OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2625                                 x_return_status       OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
2626 IS
2627 BEGIN
2628 
2629         -- initialize the error stack
2630         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_location_details');
2631         -- initialize the return  status to success
2632         x_return_status := FND_API.G_RET_STS_SUCCESS;
2633 
2634         IF p_location_id IS NOT NULL  then
2635 
2636                 SELECT address_line_1,
2637                        address_line_2,
2638                        address_line_3,
2639                        town_or_city,
2640                        postal_code,
2641                        country
2642                 INTO   x_address_line_1,
2643                        x_address_line_2,
2644                        x_address_line_3,
2645                        x_town_or_city,
2646                        x_postal_code,
2647                        x_country
2648                 FROM   hr_locations
2649                 WHERE  location_id   = p_location_id;
2650 
2651         ELSE
2652                x_address_line_1 := null;
2653                x_address_line_2 := null;
2654                x_address_line_3 := null;
2655                x_town_or_city := null;
2656                x_postal_code := null;
2657                x_country := null;
2658         END IF;
2659 
2660         -- reset the error stack
2661         PA_DEBUG.reset_err_stack;
2662 
2663 EXCEPTION
2664         WHEN  NO_DATA_FOUND THEN
2665                 x_address_line_1 := null;
2666                 x_address_line_2 := null;
2667                 x_address_line_3 := null;
2668                 x_town_or_city := null;
2669                 x_postal_code := null;
2670                 x_country := null;
2671                 x_return_status := FND_API.G_RET_STS_ERROR;
2672 
2673         WHEN OTHERS THEN
2674         -- RESET OUT PARAMS 4537865
2675         x_address_line_1 := null;
2676                 x_address_line_2 := null;
2677                 x_address_line_3 := null;
2678                 x_town_or_city := null;
2679                 x_postal_code := null;
2680                 x_country := null;
2681 
2682                 -- set the exception message and stack
2683                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.get_location_details'
2684                                         ,PA_DEBUG.g_err_stack);
2685                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2686                 raise;
2687 
2688 END get_location_details;
2689 
2690 --  PROCEDURE
2691 --              Get_Org_Defaults
2692 --  PURPOSE
2693 --              This procedure returns the default operating unit and default
2694 --              calendar for an organization
2695 --
2696 --  HISTORY
2697 --              10-MAY-2001  created  virangan
2698 --
2699 PROCEDURE get_org_defaults (p_organization_id           IN  NUMBER,
2700                             x_default_ou                OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
2701                             x_default_cal_id            OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
2702                             x_return_status             OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
2703 IS
2704 BEGIN
2705 
2706         -- initialize the error stack
2707         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_org_defaults');
2708         -- initialize the return  status to success
2709         x_return_status := FND_API.G_RET_STS_SUCCESS;
2710 
2711         IF p_organization_id IS NOT NULL  then
2712                 -- split into two separate selects - one for OU and one
2713                 -- for Calendar
2714 
2715                 BEGIN
2716                 SELECT to_number(ou.org_information1)
2717                 INTO   x_default_ou
2718                 FROM   hr_organization_information ou
2719                 WHERE  ou.org_information_context = 'Exp Organization Defaults'
2720                 AND    ou.organization_id         = p_organization_id
2721                 AND    rownum                  = 1;
2722 
2723                 EXCEPTION WHEN OTHERS THEN
2724                    x_default_ou := NULL;
2725                 END;
2726 
2727                 BEGIN
2728                 SELECT to_number(cal.org_information1)
2729                 INTO   x_default_cal_id
2730                 FROM   hr_organization_information cal-- R12 HR Org Info change
2731                 WHERE  cal.organization_id         = p_organization_id
2732                 AND    cal.org_information_context = 'Resource Defaults'
2733                 AND    rownum                      = 1;
2734 
2735                 EXCEPTION WHEN OTHERS THEN
2736                    x_default_cal_id := NULL;
2737                 END;
2738         ELSE
2739                x_default_ou := null;
2740                x_default_cal_id := null;
2741         END IF;
2742 
2743         -- reset the error stack
2744         PA_DEBUG.reset_err_stack;
2745 
2746 EXCEPTION
2747         WHEN  NO_DATA_FOUND THEN
2748                 x_default_ou := null;
2749                 x_default_cal_id := null;
2750 
2751         WHEN OTHERS THEN
2752 
2753         -- RESET OUT PARAMS 4537865
2754         x_default_ou := null;
2755                 x_default_cal_id := null;
2756 
2757                 -- set the exception message and stack
2758                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.get_org_defaults'
2759                                         ,PA_DEBUG.g_err_stack);
2760                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2761                 raise;
2762 
2763 END get_org_defaults;
2764 
2765 
2766 --  PROCEDURE
2767 --              Check_Exp_Org
2768 --  PURPOSE
2769 --              This procedure checks if an organization belongs
2770 --              to an expenditure hierarchy or not
2771 --
2772 --  HISTORY
2773 --              10-MAY-2001  created  virangan
2774 --
2775 --              04-DEC-2002  sacgupta Bug#2673140.Table pa_implementations is included to check Expenditure organization.
2776 --              28-MAR-2003  sacgupta Bug#2876296. Reverted the fix done for bug#2673140.
2777 --                                    The fix for the bug#2673140 has resulted in other
2778 --                                    issues related to resource pull.
2779 PROCEDURE Check_Exp_Org (p_organization_id   IN  NUMBER,
2780                          x_valid             OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2781                          x_return_status     OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
2782 IS
2783 BEGIN
2784 
2785         -- initialize the error stack
2786         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.check_exp_org');
2787         -- initialize the return  status to success
2788         x_return_status := FND_API.G_RET_STS_SUCCESS;
2789 
2790         x_valid := 'N';
2791         IF p_organization_id IS NOT NULL  then
2792 
2793 -- Commented out for bug 2876296
2794 /*
2795                 SELECT 'Y'
2796                 INTO   x_valid
2797                 FROM   pa_all_organizations o,
2798                        pa_implementations  i                 -- Added for bug 2673140
2799                 WHERE  o.pa_org_use_type = 'EXPENDITURES'
2800                 AND    o.inactive_date is null
2801                 AND    o.organization_id = p_organization_id
2802                 AND    rownum          = 1
2803                 AND    o.org_id = i.org_id;                 -- Added for bug 2673140
2804 */
2805 
2806                   SELECT 'Y'
2807                   INTO   x_valid
2808                   FROM   pa_all_organizations
2809                   WHERE  pa_org_use_type = 'EXPENDITURES'
2810                   AND    inactive_date is null
2811                   AND    organization_id = p_organization_id
2812                   AND    rownum          = 1;
2813 
2814         END IF;
2815 
2816         -- reset the error stack
2817         PA_DEBUG.reset_err_stack;
2818 
2819 EXCEPTION
2820         WHEN  NO_DATA_FOUND THEN
2821                 x_valid := 'N';
2822                 x_return_status := FND_API.G_RET_STS_ERROR;
2823 
2824         WHEN OTHERS THEN
2825 
2826         -- RESET OUT PARAMS : 4537865
2827 
2828                  x_valid := 'N';
2829 
2830                 -- set the exception message and stack
2831                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.check_exp_org'
2832                                         ,PA_DEBUG.g_err_stack);
2833                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2834                 raise;
2835 
2836 END check_exp_org;
2837 
2838 
2839 --  PROCEDURE
2840 --              Check_Res_Exists
2841 --  PURPOSE
2842 --              This procedure checks if a person exists in PA
2843 --              giver a person_id
2844 --
2845 --  HISTORY
2846 --              10-MAY-2001  virangan   Created
2847 --              28-MAR-2001  adabdull   Added parameter p_party_id and set
2848 --                                      this and p_person_id with default null
2849 --
2850 PROCEDURE Check_Res_Exists (p_person_id         IN  NUMBER,
2851                             p_party_id          IN  NUMBER,
2852                             x_valid             OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
2853                             x_return_status     OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
2854 IS
2855 BEGIN
2856 
2857         -- initialize the error stack
2858         PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.check_res_exists');
2859         -- initialize the return  status to success
2860         x_return_status := FND_API.G_RET_STS_SUCCESS;
2861 
2862         x_valid := 'N';
2863         IF p_person_id IS NOT NULL  then
2864 
2865                 SELECT 'Y'
2866                 INTO   x_valid
2867                 FROM   pa_resource_txn_attributes
2868                 WHERE  person_id = p_person_id
2869                 AND    rownum          = 1;
2870 
2871         ELSIF p_party_id IS NOT NULL then
2872 
2873                 SELECT 'Y'
2874                 INTO   x_valid
2875                 FROM   pa_resource_txn_attributes
2876                 WHERE  party_id = p_party_id
2877                 AND    rownum = 1;
2878 
2879         END IF;
2880 
2881         -- reset the error stack
2882         PA_DEBUG.reset_err_stack;
2883 
2884 EXCEPTION
2885         WHEN  NO_DATA_FOUND THEN
2886                 x_valid := 'N';
2887                 x_return_status := FND_API.G_RET_STS_ERROR;
2888 
2889         WHEN OTHERS THEN
2890         --4537865 RESET OUT PARAMS
2891          x_valid := 'N';
2892 
2893                 -- set the exception message and stack
2894                 FND_MSG_PUB.add_exc_msg('PA_RESOURCE_UTILS.check_res_exists'
2895                                         ,PA_DEBUG.g_err_stack);
2896                 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
2897                 raise;
2898 
2899 END check_res_exists;
2900 
2901 --  FUNCTION
2902 --           Get_Org_Prim_Contact_Name
2903 --  PURPOSE
2904 --           This function returns the primary contact name of the given organzation
2905 --  HISTORY
2906 --           11-JUL-2001 snam  Created
2907 FUNCTION Get_Org_Prim_Contact_Name(p_org_id   IN NUMBER,
2908                                    p_prim_role_name IN VARCHAR2) RETURN VARCHAR2
2909 IS
2910 
2911 BEGIN
2912 
2913    RETURN PA_RESOURCE_UTILS.G_PRIMARY_CONTACT_NAME;
2914 
2915 END get_org_prim_contact_name;
2916 
2917 
2918 --  FUNCTION
2919 --           Get_Org_Prim_Contact_Id
2920 --  PURPOSE
2921 --           This function returns the primary_contact_id of the org which has been queried
2922 --           in the function 'Get_Org_Prim_Contact_Name'. This function should be used only
2923 --           after calling the funtion 'Get_Org_Prim_Contact_Name'.
2924 --  HISTORY
2925 --           27-AUG-2001 snam  Created
2926 FUNCTION Get_Org_Prim_Contact_Id(p_org_id   IN NUMBER,
2927                                  p_prim_role_name IN VARCHAR2) RETURN NUMBER
2928 IS
2929    l_primary_contact_name VARCHAR2(240) := NULL;
2930    l_primary_contact_id NUMBER;
2931    l_menu_id            NUMBER; /* Bug# 2499051 */
2932 BEGIN
2933    -- reset primary_contact_id before set it up again
2934    PA_RESOURCE_UTILS.G_PRIMARY_CONTACT_NAME:= NULL;
2935 
2936 /* Bug# 2499051 */
2937    select pa_security_pvt.get_menu_id(p_prim_role_name)
2938    into   l_menu_id
2939    from   dual;
2940 /* Bug# 2499051 */
2941 
2942    SELECT pep.full_name,
2943           pep.person_id
2944    INTO  l_primary_contact_name,
2945          l_primary_contact_id
2946    FROM  fnd_grants fg,
2947          fnd_objects fob,
2948          per_all_people_f pep, -- Bug 4684198 - use base table not secure view
2949          wf_roles wfr
2950   /* Bug# 2499051 - Moved the function call to fetch to a local variable at the start of the procedure
2951          (select pa_security_pvt.get_menu_id(p_prim_role_name) menu_id from dual) temp */
2952    WHERE  fg.object_id = fob.object_id
2953           AND  fob.obj_name = 'ORGANIZATION'
2954           AND  fg.instance_pk1_value = to_char(p_org_id)
2955 /*        AND  fg.menu_id = temp.menu_id -- Bug# 2499051 - Using local variable */
2956           AND  fg.menu_id = l_menu_id /* Bug# 2499051 */
2957           AND  fg.instance_type = 'INSTANCE'
2958           AND  fg.grantee_type = 'USER'
2959           AND  trunc(SYSDATE) BETWEEN trunc(fg.start_date)
2960                               AND     trunc(NVL(fg.end_date, SYSDATE+1))
2961         --  AND  'PER:' || pep.person_id = fg.grantee_key --bug 2795616:perfomance
2962           AND    fg.grantee_key   = wfr.name
2963           AND    wfr.orig_system  = 'HZ_PARTY'
2964           AND    pep.party_id = wfr.orig_system_id -- Added for 11.5.10 security
2965           -- AND PEP.PERSON_ID  = substr(fg.grantee_key,instr(fg.grantee_key,':')+1)
2966           AND  sysdate BETWEEN pep.effective_start_date
2967                AND pep.effective_end_date
2968           AND (pep.current_employee_flag = 'Y' OR pep.current_npw_flag = 'Y'); -- Added for bug 4938392
2969 
2970    -- set primary_contact_name to the global variable to get it later
2971    -- from the function 'Get_Org_Prim_Contact_Name'
2972    PA_RESOURCE_UTILS.G_PRIMARY_CONTACT_NAME := l_primary_contact_name;
2973 
2974    RETURN l_primary_contact_id;
2975 
2976    EXCEPTION
2977         WHEN  NO_DATA_FOUND THEN
2978            RETURN l_primary_contact_id;
2979         WHEN OTHERS THEN
2980            RETURN l_primary_contact_id;
2981 
2982 END Get_Org_Prim_Contact_Id;
2983 
2984 --  FUNCTION
2985 --              Is_Future_Resource
2986 --  PURPOSE
2987 --              This procedure checks if a person has only future
2988 --              records in pa_resources_denorm
2989 --
2990 --  HISTORY
2991 --              31-AUG-2001  created  virangan
2992 --
2993 FUNCTION Is_Future_Resource (p_resource_id IN NUMBER)
2994     RETURN VARCHAR2
2995 IS
2996    l_future_res VARCHAR2(1) := 'Y';
2997    l_start_date DATE;
2998 BEGIN
2999 
3000     SELECT min(resource_effective_start_date)
3001     INTO l_start_date
3002     FROM pa_resources_denorm
3003     WHERE resource_id = p_resource_id
3004     ;
3005 
3006     IF l_start_date <= sysdate THEN
3007        l_future_res := 'N';
3008     ELSE
3009        l_future_res := 'Y';
3010     END IF;
3011 
3012     RETURN l_future_res;
3013 
3014 EXCEPTION
3015     WHEN NO_DATA_FOUND THEN
3016         RETURN l_future_res;
3017     WHEN OTHERS THEN
3018         RETURN null;
3019 
3020 END Is_Future_Resource;
3021 
3022 --  FUNCTION
3023 --              Is_Future_Rehire -- Added for bug 8988264
3024 --  PURPOSE
3025 --              This procedure checks if a person has
3026 --              records in pa_resources_denorm for a rehire scenario.
3027 --
3028 --  HISTORY
3029 --              28-DEC-2009  created  skkoppul
3030 --
3031 FUNCTION Is_Future_Rehire (p_resource_id IN NUMBER)
3032         RETURN VARCHAR2
3033 IS
3034    l_future_reh VARCHAR2(1) := 'N';
3035    l_start_date DATE;
3036 BEGIN
3037 
3038     SELECT min(resource_effective_start_date)
3039         INTO l_start_date
3040     FROM pa_resources_denorm
3041         WHERE resource_id = p_resource_id
3042         and resource_effective_start_date > sysdate
3043         ;
3044 
3045         IF l_start_date > sysdate THEN
3046            l_future_reh := 'Y';
3047         END IF;
3048 
3049     RETURN l_future_reh;
3050 
3051 EXCEPTION
3052     WHEN NO_DATA_FOUND THEN
3053       l_future_reh := 'N';
3054         RETURN l_future_reh;
3055     WHEN OTHERS THEN
3056         RETURN null;
3057 
3058 END Is_Future_Rehire;
3059 
3060 --  FUNCTION
3061 --              Is_Past_Resource
3062 --  PURPOSE
3063 --              This procedure checks if a person has only past
3064 --              records in pa_resources_denorm
3065 --
3066 --  HISTORY
3067 --              01-JAN-2009  created  asahoo
3068 --
3069 FUNCTION Is_Past_Resource (p_resource_id IN NUMBER)
3070     RETURN VARCHAR2
3071 IS
3072    l_past_res VARCHAR2(1) := 'N';
3073    l_end_date DATE;
3074 BEGIN
3075 
3076     SELECT max(resource_effective_end_date)
3077     INTO l_end_date
3078     FROM pa_resources_denorm
3079     WHERE resource_id = p_resource_id ;
3080 
3081     IF l_end_date < sysdate THEN
3082        l_past_res := 'Y';
3083     ELSE
3084        l_past_res := 'N';
3085     END IF;
3086 
3087     RETURN l_past_res;
3088 
3089 EXCEPTION
3090     WHEN OTHERS THEN
3091         RETURN null;
3092 
3093 END Is_Past_Resource;
3094 
3095 
3096 --  FUNCTION
3097 --              Get_Resource_Start_date
3098 --  PURPOSE
3099 --              This procedure returns the start date of the resource
3100 --              in pa_resources_denorm
3101 --
3102 --  HISTORY
3103 --              31-AUG-2001  created  virangan
3104 --
3105 FUNCTION Get_Resource_Start_Date (p_resource_id IN NUMBER)
3106     RETURN DATE
3107 IS
3108 
3109     l_start_date DATE;
3110 
3111 BEGIN
3112 
3113     SELECT min(resource_effective_start_date)
3114     INTO   l_start_date
3115     FROM   pa_resources_denorm
3116     WHERE  resource_id = p_resource_id
3117     ;
3118 
3119     RETURN l_start_date;
3120 
3121 EXCEPTION
3122     WHEN NO_DATA_FOUND THEN
3123         RETURN l_start_date;
3124     WHEN OTHERS THEN
3125         RETURN null;
3126 END Get_Resource_Start_Date;
3127 
3128 --  FUNCTION
3129 --              Get_Resource_Start_date_rehire -- Added for bug 8988264
3130 --  PURPOSE
3131 --              This procedure returns the start date of the resource
3132 --              in pa_resources_denorm for rehires
3133 --
3134 --  HISTORY
3135 --              28-DEC-2009  created  skkoppul
3136 --
3137 FUNCTION Get_Resource_Start_Date_Rehire (p_resource_id IN NUMBER)
3138         RETURN DATE
3139 IS
3140 
3141         l_start_date DATE;
3142 
3143 BEGIN
3144 
3145     SELECT min(resource_effective_start_date)
3146     INTO   l_start_date
3147     FROM   pa_resources_denorm
3148     WHERE  resource_id = p_resource_id
3149     and resource_effective_start_date > sysdate
3150     ;
3151 
3152     RETURN l_start_date;
3153 
3154 EXCEPTION
3155         WHEN NO_DATA_FOUND THEN
3156         RETURN l_start_date;
3157     WHEN OTHERS THEN
3158         RETURN null;
3159 END Get_Resource_Start_Date_Rehire;
3160 
3161 -- start for bug#9233998
3162 --  FUNCTION
3163 --              Get_Resource_end_date
3164 --  PURPOSE
3165 --              This procedure returns the end date of the resource
3166 --              in pa_resources_denorm
3167 --
3168 --  HISTORY
3169 --              28-10-2009 NISINHA Created
3170 --
3171 FUNCTION Get_Resource_end_Date (p_resource_id IN NUMBER)
3172     RETURN DATE
3173 IS
3174 
3175     l_end_date DATE;
3176 
3177 BEGIN
3178 
3179     SELECT max(resource_effective_end_date)
3180     INTO   l_end_date
3181     FROM   pa_resources_denorm
3182     WHERE  resource_id = p_resource_id
3183     ;
3184 
3185     RETURN l_end_date;
3186 
3187 EXCEPTION
3188     WHEN NO_DATA_FOUND THEN
3189         RETURN l_end_date;
3190     WHEN OTHERS THEN
3191         RETURN null;
3192 END Get_Resource_end_Date;
3193 -- end for bug#9233998
3194 
3195 --  FUNCTION
3196 --              Get_Resource_Effective_date
3197 --  PURPOSE
3198 --              This procedure returns the effective date of the resource
3199 --              in pa_resources_denorm. This is the resource_effective_start_date
3200 --              for a future resource or sysdate for active resources
3201 --
3202 --  HISTORY
3203 --              17-SEP-2001  created  virangan
3204 --
3205 FUNCTION Get_Resource_Effective_Date (p_resource_id IN NUMBER)
3206     RETURN DATE
3207 IS
3208 
3209     l_start_date DATE := sysdate;
3210 
3211 BEGIN
3212 
3213     IF is_future_resource( p_resource_id ) = 'Y' THEN
3214         l_start_date := get_resource_start_date( p_resource_id );
3215     ELSE
3216     -- made changes for 8988264 : skkoppul
3217         IF is_future_rehire(p_resource_id) = 'Y' THEN
3218            l_start_date := get_resource_start_date_rehire(p_resource_id);
3219         ELSE
3220            l_start_date := sysdate;
3221         END IF;
3222     END IF;
3223 
3224     RETURN l_start_date;
3225 
3226 EXCEPTION
3227     WHEN OTHERS THEN
3228         RETURN l_start_date;
3229 
3230 END Get_Resource_Effective_Date;
3231 
3232 
3233 --  FUNCTION
3234 --              Get_Person_Start_date
3235 --  PURPOSE
3236 --              This procedure returns the start date of the person
3237 --              in per_all_people_f
3238 --
3239 --  HISTORY
3240 --              21-jan-2003  created  sramesh for the bug 2686120
3241 --
3242 FUNCTION Get_Person_Start_Date (p_person_id IN NUMBER)
3243     RETURN DATE
3244 IS
3245 
3246     l_start_date DATE;
3247 
3248 BEGIN
3249 /* Commented for bug 4510084
3250     SELECT P.EFFECTIVE_START_DATE
3251     INTO   l_start_date
3252     FROM   PER_ALL_PEOPLE_F P
3253     WHERE  P.PERSON_ID = p_person_id
3254     AND p.EFFECTIVE_START_DATE = (SELECT MIN(PP.EFFECTIVE_START_DATE)
3255                             FROM PER_ALL_PEOPLE_F PP
3256                             WHERE PP.PERSON_ID = p_person_id
3257                             AND PP.EFFECTIVE_END_DATE >= SYSDATE)
3258                             AND (P.EMPLOYEE_NUMBER IS NOT NULL OR
3259                                      P.npw_number is not null); -- FP M CWK
3260 End for bug 4510084*/
3261 
3262 /* Added for bug 4510084 */
3263      SELECT MIN(PP.EFFECTIVE_START_DATE)
3264      INTO   l_start_date
3265          FROM PER_ALL_PEOPLE_F PP
3266          WHERE PP.PERSON_ID = p_person_id
3267      AND (PP.CURRENT_EMPLOYEE_FLAG='Y' OR PP.CURRENT_NPW_FLAG = 'Y')
3268          AND (PP.EMPLOYEE_NUMBER IS NOT NULL OR
3269                PP.npw_number is not null);-- FP M CWK
3270 
3271 /* End for bug 4510084 */
3272 
3273     RETURN l_start_date;
3274 
3275 EXCEPTION
3276     WHEN NO_DATA_FOUND THEN
3277         RETURN null;  /*Commented the code for bug 3071483 l_start_date*/
3278     WHEN OTHERS THEN
3279         RETURN null;
3280 END Get_Person_Start_Date;
3281 
3282 --
3283 --  PROCEDURE
3284 --              Get_Res_Capacity
3285 --  PURPOSE
3286 --              This procedure does the following
3287 --              For the given Resource Id, start date and end date
3288 --              gets the capacity hours for the resource
3289 --  HISTORY
3290 --              04-SEP-2001 Vijay Ranganathan    created
3291 --
3292 FUNCTION  get_res_capacity( p_resource_id          IN      NUMBER,
3293                             p_start_date           IN      DATE,
3294                             p_end_date             IN      DATE)
3295 RETURN NUMBER
3296 IS
3297 l_capacity        NUMBER;
3298 
3299 BEGIN
3300 
3301 
3302   BEGIN
3303 
3304      SELECT sum(capacity_quantity)
3305      INTO   l_capacity
3306      FROM   pa_forecast_items
3307      WHERE  resource_id      = p_resource_id
3308      AND    delete_flag      = 'N'
3309      AND    forecast_item_type = 'U'
3310      AND    item_date  between p_start_date
3311                        and     p_end_date;
3312   EXCEPTION
3313         WHEN NO_DATA_FOUND THEN
3314              l_capacity := 0;
3315   END;
3316 
3317 
3318    RETURN l_capacity;
3319 EXCEPTION
3320    WHEN OTHERS THEN
3321         RETURN 0;
3322 END get_res_capacity;
3323 
3324 --
3325 --  PROCEDURE
3326 --              Get_Res_Wk_Capacity
3327 --  PURPOSE
3328 --              This procedure does the following
3329 --              For the given Resource Id, week date date
3330 --              gets the capacity hours for the resource
3331 --  HISTORY
3332 --              13-SEP-2001 Vijay Ranganathan    created
3333 --
3334  FUNCTION  get_res_wk_capacity( p_resource_id          IN      NUMBER,
3335                                 p_wk_date              IN      DATE)
3336   RETURN NUMBER
3337   IS
3338   l_calendar_id     NUMBER;
3339   x_capacity        NUMBER;
3340   l_organization_id NUMBER;
3341   l_default_ou      NUMBER;
3342   l_return_status   VARCHAR2(30);
3343 
3344  BEGIN
3345 
3346     ---------------------------------------------------------------------
3347     --If Future resource use organization calendar, otherwise use resources
3348     --JTF calendar
3349     ----------------------------------------------------------------------
3350     IF pa_resource_utils.is_future_resource ( p_resource_id ) = 'Y' THEN
3351 
3352        --dbms_output.put_line('Future Resource');
3353 
3354        BEGIN
3355           SELECT resource_organization_id
3356           INTO   l_organization_id
3357           FROM   pa_resources_denorm
3358           WHERE  p_wk_date BETWEEN resource_effective_start_date AND resource_effective_end_date
3359           AND    resource_id = p_resource_id  ;
3360 
3361        EXCEPTION
3362           WHEN NO_DATA_found THEN
3363             --dbms_output.put_line('Organization is null');
3364             l_organization_id := NULL;
3365        END;
3366 
3367        --dbms_output.put_line('Resource Organization Id: ' || l_organization_id);
3368 
3369        pa_resource_utils.get_org_defaults ( P_ORGANIZATION_ID   => l_organization_id,
3370                                             X_DEFAULT_OU        => l_default_ou,
3371                                             X_DEFAULT_CAL_ID    => l_calendar_id,
3372                                             X_RETURN_STATUS     => l_return_status);
3373 
3374        --dbms_output.put_line('Calendar Id: ' || l_calendar_id);
3375 
3376        IF l_calendar_id IS NULL THEN
3377           l_calendar_id := fnd_profile.value_specific('PA_PRM_DEFAULT_CALENDAR');
3378        END IF;
3379 
3380     ELSE --If not a future resource
3381 
3382        BEGIN
3383 
3384            SELECT jcra.calendar_id
3385            INTO   l_calendar_id
3386            FROM   pa_resources par,
3387                   jtf_cal_resource_assign jcra
3388            WHERE  par.jtf_resource_id = jcra.resource_id
3389            AND    par.resource_id     = p_resource_id
3390            AND    p_wk_date between jcra.start_date_time and nvl(jcra.end_date_time,to_date('31-12-4712', 'DD-MM-YYYY'));
3391 
3392        EXCEPTION
3393           WHEN no_data_found THEN
3394              l_calendar_id := NULL;
3395        END;
3396 
3397     END IF;
3398 
3399     --dbms_output.put_line('Calendar Id: ' || l_calendar_id);
3400 
3401     -------------------------------------------------------------
3402     --Calculate capacity for the given day once calendar is known
3403     -------------------------------------------------------------
3404     BEGIN
3405         SELECT decode( to_char( p_wk_date,'D'),
3406                         '1',SUNDAY_HOURS,
3407                         '2',MONDAY_HOURS,
3408                         '3',TUESDAY_HOURS,
3409                         '4',WEDNESDAY_HOURS,
3410                         '5',THURSDAY_HOURS,
3411                         '6',FRIDAY_HOURS,
3412                             SATURDAY_HOURS )
3413         INTO  x_capacity
3414         FROM  pa_schedules pas
3415         WHERE p_wk_date BETWEEN pas.start_date AND pas.end_date
3416         AND   pas.SCHEDULE_TYPE_CODE = 'CALENDAR'
3417         AND   pas.CALENDAR_ID        = l_calendar_id
3418         ;
3419     EXCEPTION
3420        WHEN OTHERS THEN
3421            x_capacity := 0;
3422     END;
3423 
3424   RETURN x_capacity;
3425 
3426  EXCEPTION
3427     WHEN OTHERS THEN
3428    RETURN 0;
3429 
3430  END get_res_wk_capacity;
3431 
3432 --  FUNCTION
3433 --              get_pa_logged_user
3434 --  PURPOSE
3435 --              This procedure checks if logged user is
3436 --              Project Super User or Resource Manager
3437 --              or Staffing Manager
3438 --
3439 --  HISTORY
3440 --              25-SEP-2001  created  virangan
3441 --
3442 FUNCTION get_pa_logged_user (p_authority IN VARCHAR2)
3443     RETURN VARCHAR2
3444 IS
3445 
3446     l_menu_name varchar2(255);
3447     l_pa_logged_user varchar2(2) := 'SM'; -- 'TM'; // changed back to SM for 8403781 -- 'SM'; // Bug 7500918
3448     is_project_super_user varchar2(1);
3449 
3450 BEGIN
3451     -- If p_authority is 'RESOURCE', check PA_SUPER_RESOURCE profile option
3452     -- If p_authority is 'PROJECT', check PA_SUPER_PROJECT_VIEW profile option
3453 
3454     IF p_authority = 'RESOURCE' THEN
3455       is_project_super_user := fnd_profile.value_specific('PA_SUPER_RESOURCE',
3456                                                            fnd_global.user_id,
3457                                                            fnd_global.resp_id,
3458                                                            fnd_global.resp_appl_id) ;
3459     ELSE
3460       is_project_super_user := fnd_profile.value_specific('PA_SUPER_PROJECT_VIEW',
3461                                                            fnd_global.user_id,
3462                                                            fnd_global.resp_id,
3463                                                            fnd_global.resp_appl_id) ;
3464     END IF;
3465 
3466     if is_project_super_user = 'Y' then
3467         return 'SU';
3468     end if;
3469      /* resp.application_id = fnd_global.resp_appl_id join is added for Perfomance
3470         Bug 2634995        */
3471     select menu_name
3472     into   l_menu_name
3473     from   fnd_menus menu,
3474            fnd_responsibility resp
3475     where  resp.responsibility_id = fnd_global.resp_id
3476     and    resp.menu_id           = menu.menu_id
3477     and    resp.application_id = fnd_global.resp_appl_id ;
3478 
3479 
3480     /* changed for bug 2775111: recently the function 'PA_STAFF_HOME_RM'
3481        got moved from menu 'PA_PRM_RES_MGR' to the submenu 'PA_STAFFING_RES_MGR'.
3482        Since FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS doesn't work recursively,
3483        we needed use new submenu to tell the login resp of resource manager.
3484      if FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
3485            menu_name          => l_menu_name,
3486            sub_menu_name      => '',
3487            function_name      => 'PA_STAFF_HOME_RM')  */
3488 
3489     if FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
3490            menu_name          => l_menu_name,
3491            sub_menu_name      => 'PA_STAFFING_RES_MGR',
3492            function_name      => '')
3493     then
3494            l_pa_logged_user := 'RM';
3495 
3496     elsif FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
3497            menu_name          => l_menu_name,
3498            sub_menu_name      => '',
3499            function_name      => 'PA_STAFF_HOME')
3500     then
3501            l_pa_logged_user := 'SM';
3502     end if;
3503 
3504     return l_pa_logged_user;
3505 
3506 EXCEPTION
3507     WHEN NO_DATA_FOUND THEN
3508         RETURN 'SU';
3509     WHEN OTHERS THEN
3510         RETURN null;
3511 
3512 END get_pa_logged_user;
3513 
3514 --
3515 --  PROCEDURE
3516 --              Get_Provisional_hours
3517 --  PURPOSE
3518 --              This procedure gets the provisional hours
3519 --              for a resource on a given date
3520 --  HISTORY
3521 --              22-OCT-2001 Vijay Ranganathan    created
3522 --
3523 FUNCTION get_provisional_hours
3524     ( p_resource_id IN Number,
3525       p_Week_date IN DATE)
3526 RETURN NUMBER
3527 IS
3528 
3529 l_date DATE;
3530 l_date2 DATE;
3531 l_resource_id NUMBER;
3532 
3533 BEGIN
3534 
3535      select pfi.global_exp_period_end_date,
3536             pfi.item_date,
3537             sum(decode(pfi.provisional_flag,'Y',pfi.item_quantity,0)),
3538             sum(decode(pfi.provisional_flag,'N',pfi.item_quantity,0)),
3539             pfi.resource_id
3540      into   l_date,
3541             l_date2,
3542             g_provisional_hours,
3543             g_confirmed_hours,
3544             l_resource_id
3545   from   pa_forecast_items pfi
3546   where  pfi.forecast_item_type = 'A'
3547   and    pfi.delete_flag        = 'N'
3548   and    pfi.resource_id        = p_resource_id
3549   and    pfi.item_date          = p_week_date
3550   group by pfi.global_exp_period_end_date,
3551            pfi.item_date,
3552            pfi.resource_id;
3553 
3554   return g_provisional_hours;
3555 
3556 END;
3557 
3558 --
3559 --  PROCEDURE
3560 --              Get_Confirmed_hours
3561 --  PURPOSE
3562 --              This procedure gets the confirmed hours
3563 --              for a resource based on the date set in
3564 --              the get_provisional_hours call
3565 --  HISTORY
3566 --              22-OCT-2001 Vijay Ranganathan    created
3567 --
3568 FUNCTION get_confirmed_hours
3569 RETURN NUMBER
3570 IS
3571 BEGIN
3572     RETURN g_confirmed_hours;
3573 END;
3574 
3575 --+
3576 --  FUNCTION
3577 --           check_user_has_res_auth
3578 --  PURPOSE
3579 --           This function checks if the given user has resource authority
3580 --           over the specified resource
3581 --  HISTORY
3582 --           03-OCT-2001 virangan  Created
3583 --           05-SEP-2002 adabdull  Modified to support resource supervisor
3584 --                                 hierarchy
3585 --+
3586 FUNCTION check_user_has_res_auth (p_user_person_id  IN NUMBER
3587                                  ,p_resource_id     IN NUMBER ) RETURN VARCHAR2
3588 IS
3589 
3590   l_res_auth     VARCHAR2(1) := 'N';
3591   l_resource_id  NUMBER      := p_resource_id;
3592   l_manager_id   NUMBER      := p_user_person_id;
3593 
3594   -- this cursor checks whether the person is the Resource Manager of
3595   -- the resource in the supervisor hierarchy
3596   -- Bug # 10323891 begin. Reverting back the changes.
3597   CURSOR check_res_mgr IS
3598      SELECT 'Y'
3599      FROM pa_resources_denorm
3600      WHERE sysdate    < resource_effective_end_date
3601      AND   manager_id = l_manager_id
3602      START WITH resource_id = l_resource_id
3603      CONNECT BY
3604           prior manager_id = person_id
3605           and manager_id <> prior person_id
3606           and sysdate < resource_effective_end_date
3607           and sysdate < prior resource_effective_end_date;
3608 	-- Bug # 10323891 end.
3609   -- this cursor checks whether the person is the Staffing Manager of
3610   -- the resource
3611   CURSOR check_staff_mgr IS
3612      SELECT 'Y'
3613      FROM pa_resources_denorm res,
3614           fnd_grants          fg,
3615           fnd_objects         fob,
3616           per_all_people_f    per,
3617       wf_roles            wfr,
3618           (select pa_security_pvt.get_menu_id('PA_PRM_RES_AUTH') menu_id
3619            from dual)         res_auth_menu
3620      WHERE fob.obj_name           = 'ORGANIZATION'
3621        and res.resource_id        = l_resource_id
3622        and trunc(sysdate)                < res.resource_effective_end_date --Bug 9403051
3623        and fg.instance_pk1_value  = to_char(res.resource_organization_id)
3624        and fg.instance_type       = 'INSTANCE'
3625        and fg.object_id           = fob.object_id
3626        and fg.grantee_type        = 'USER'
3627        and fg.menu_id             = res_auth_menu.menu_id
3628        and trunc(SYSDATE) between trunc(fg.start_date)
3629                           and     trunc(NVL(fg.end_date, SYSDATE+1))
3630        -- and fg.grantee_key         = 'PER:'|| per.person_id
3631        AND fg.grantee_key   = wfr.name
3632        AND wfr.orig_system  = 'HZ_PARTY'
3633        AND per.party_id     = wfr.orig_system_id -- Added for 11.5.10 security
3634        and trunc(SYSDATE) between per.effective_start_date and per.effective_end_date --Bug 9403051
3635        and per.person_id          <> res.manager_id
3636        and per.person_id          = l_manager_id;
3637 
3638 	--Bug 10323891 begin.
3639 	-- this cursor checks whether the person is an ex-employee and if yes
3640 	-- whether person was the last resource manager the supervisor hierarchy
3641 	CURSOR check_ex_emp IS
3642 		SELECT 'Y' FROM pa_resources_denorm d
3643 			 WHERE manager_id               =l_manager_id
3644 			 START WITH resource_id        =l_resource_id
3645 			 AND resource_effective_end_date =
3646 			   (SELECT MAX(resource_effective_end_date)
3647 			  FROM pa_resources_denorm t1
3648 			  WHERE t1.resource_id = l_resource_id
3649 				 )
3650 			  CONNECT BY prior manager_id = person_id
3651 				AND NVL(manager_id,-1)               <> prior person_id		-- Top most level manager's manager_id will be null.
3652 				AND prior resource_effective_end_date between resource_effective_start_date
3653 				and resource_effective_end_date; -- will pull the manager of resource at the	time of resource end date
3654 	-- Bug 10323891 end.
3655 
3656 BEGIN
3657 
3658      OPEN check_res_mgr;
3659      FETCH check_res_mgr INTO l_res_auth;
3660 
3661      IF check_res_mgr%NOTFOUND THEN
3662 
3663          OPEN check_staff_mgr;
3664          FETCH check_staff_mgr INTO l_res_auth;
3665 
3666          IF check_staff_mgr%NOTFOUND THEN
3667 
3668 			OPEN check_ex_emp;
3669 			FETCH check_ex_emp INTO l_res_auth;				-- Bug 10323891
3670 				IF check_ex_emp%NOTFOUND THEN
3671 					l_res_auth := 'N';
3672 				END IF;
3673 			CLOSE check_ex_emp;								-- Bug 10323891
3674 
3675 		 END IF;
3676          CLOSE check_staff_mgr;
3677 
3678      END IF;
3679      CLOSE check_res_mgr;
3680 
3681      RETURN l_res_auth;
3682 
3683 EXCEPTION
3684 
3685     WHEN NO_DATA_FOUND THEN
3686         RETURN l_res_auth;
3687     WHEN OTHERS THEN
3688         RETURN null;
3689 
3690 END check_user_has_res_auth;
3691 
3692 FUNCTION get_person_id(p_resource_id IN NUMBER)
3693 RETURN NUMBER
3694 IS
3695 l_person_id NUMBER;
3696 BEGIN
3697 
3698    SELECT person_id
3699    INTO l_person_id
3700    FROM pa_resource_txn_attributes
3701    WHERE resource_id = p_resource_id;
3702 
3703    RETURN l_person_id;
3704 EXCEPTION
3705   WHEN OTHERS THEN
3706        RETURN -999;
3707 END get_person_id;
3708 
3709 --
3710 --
3711 --  FUNCTION
3712 --              get_person_id_from_party_id
3713 --  PURPOSE
3714 --              This  function returns back the person_id
3715 --              for a person based on the party_id passed in.
3716 --  HISTORY
3717 --  22-OCT-2002      ramurthy
3718 --start 29-Oct-09  cklee                        Bug 8972676 - CLICKING ON ISSUE OWNER TAKES YOU TO RESOURCE DETAILS FOR ANOTHER PERSON
3719 /*
3720 FUNCTION get_person_id_from_party_id(p_party_id IN NUMBER)
3721 RETURN NUMBER
3722 IS
3723 l_person_id NUMBER;
3724 BEGIN
3725 
3726    SELECT person_id
3727    INTO l_person_id
3728    FROM per_all_people_f
3729    WHERE party_id = p_party_id
3730    AND   trunc(sysdate) between trunc(effective_start_date)
3731                             and trunc(effective_end_date);
3732 
3733    RETURN l_person_id;
3734 EXCEPTION
3735   WHEN OTHERS THEN
3736        RETURN -999;
3737 END get_person_id_from_party_id;
3738 */
3739  FUNCTION get_person_id_from_party_id(p_party_id IN NUMBER)
3740  RETURN NUMBER
3741  IS
3742 
3743    cursor p_active is
3744     SELECT person_id
3745     FROM per_all_people_f
3746     WHERE party_id = p_party_id
3747     AND   CURRENT_EMPLOYEE_FLAG = 'Y'
3748     AND   trunc(sysdate) between trunc(effective_start_date)
3749                              and trunc(effective_end_date);
3750 
3751    cursor p_teminated is
3752     SELECT person_id
3753     FROM per_all_people_f
3754     WHERE party_id = p_party_id
3755     and trunc(effective_end_date) =
3756     (select max(trunc(effective_end_date))
3757      from per_all_people_f
3758       WHERE   trunc(sysdate) not between trunc(effective_start_date)
3759                              and trunc(effective_end_date)
3760       and party_id = p_party_id);
3761 
3762  l_person_id NUMBER;
3763 
3764  BEGIN
3765 
3766     OPEN p_active;
3767     FETCH p_active INTO l_person_id;
3768     CLOSE p_active;
3769 
3770     -- IF this person has been terminated
3771     IF l_person_id IS NULL THEN
3772       OPEN p_teminated;
3773       FETCH p_teminated INTO l_person_id;
3774       CLOSE p_teminated;
3775     END IF;
3776 
3777     -- if still not able to find a person
3778     IF l_person_id IS NULL THEN
3779       l_person_id := -999;
3780     END IF;
3781     RETURN l_person_id;
3782  EXCEPTION
3783    WHEN OTHERS THEN
3784         RETURN -999;
3785  END get_person_id_from_party_id;
3786 --end:-- 29-Oct-09  cklee                        Bug 8972676 - CLICKING ON ISSUE OWNER TAKES YOU TO RESOURCE DETAILS FOR ANOTHER PERSON
3787 --  PROCEDURE
3788 --              check_res_not_terminated
3789 --  PURPOSE
3790 --              This function returns true if the person has not been
3791 --              terminated and false if it is a terminated employee.
3792 --  HISTORY
3793 --  14-FEB-2003 ramurthy  Created
3794 FUNCTION check_res_not_terminated(p_object_type          IN VARCHAR2,
3795                                   p_object_id            IN NUMBER,
3796                                   p_effective_start_date IN DATE)
3797 RETURN BOOLEAN IS
3798 
3799   cursor chk_no_termination(p_person_id NUMBER) is
3800    select 'Y'
3801    from per_all_people_f per
3802    where per.person_id             = p_person_id
3803      and (per.current_employee_flag = 'Y' OR per.current_npw_flag = 'Y')
3804      and p_effective_start_date between per.effective_start_date
3805                                     and per.effective_end_date;
3806 l_chk VARCHAR2(1) := 'N';
3807 
3808 BEGIN
3809 IF p_object_type = 'PERSON' THEN
3810    open chk_no_termination(p_object_id);
3811    fetch chk_no_termination into l_chk;
3812    close chk_no_termination;
3813 
3814    IF l_chk = 'Y' THEN
3815       return true;
3816    ELSE
3817       return false;
3818    END IF;
3819 ELSE
3820    return false;
3821 END IF;
3822 END check_res_not_terminated;
3823 
3824 --
3825 --
3826 --  PROCEDURE
3827 --           validate_person
3828 --  PURPOSE
3829 --           This procedure checks if the resource is valid as of the assignment
3830 --           start date in the pa_resources_denorm table
3831 --  HISTORY
3832 --           26-FEB-2002 adabdull Created
3833 --
3834 PROCEDURE validate_person (   p_person_id             IN NUMBER,
3835                               p_start_date            IN DATE,
3836                               x_return_status         OUT NOCOPY VARCHAR2)                  --File.Sql.39 bug 4440895
3837 IS
3838    l_assignment_id    NUMBER;
3839    l_job_id           NUMBER;
3840    l_person_type      VARCHAR2(30);
3841    l_person_id        NUMBER;
3842 
3843 /* Bug#2683266-Commented the cursor get_person_type and added cursor
3844 
3845    cursor get_person_type
3846    is
3847    select person_id
3848    from per_people_f per,
3849         per_person_types ptype
3850    where per.person_id             = p_person_id
3851    and   per.person_type_id        = ptype.person_type_id
3852    and   (ptype.system_person_type  = 'EMP'
3853           OR ptype.system_person_type = 'EMP_APL');
3854 
3855 End of comment for bug#2683266 */
3856 
3857 /* New cursor validate_person_type added for bug#2683266 */
3858 
3859    cursor validate_person_type
3860    is
3861    select person_id
3862    from per_all_people_f per
3863    where per.person_id             = p_person_id
3864      and (per.current_employee_flag = 'Y' OR per.current_npw_flag = 'Y');
3865 
3866    cursor get_active_assignment
3867    is
3868    select asgn.assignment_id
3869    from per_all_assignments_f asgn,
3870         per_assignment_status_types status,
3871         (select person_id, actual_termination_date
3872            from per_periods_of_service
3873          union all
3874          select person_id, actual_termination_date
3875            from per_periods_of_placement) po -- FP M CWK
3876    where asgn.person_id                  = p_person_id
3877    and   nvl(po.actual_termination_date, trunc(sysdate)) >= trunc(sysdate)
3878    and   asgn.person_id                  = po.person_id
3879    and   po.person_id                    = p_person_id
3880    and   asgn.assignment_status_type_id  = status.assignment_status_type_id
3881    and   status.per_system_status in ('ACTIVE_ASSIGN', 'ACTIVE_CWK')
3882    and   p_start_date between asgn.effective_start_date
3883                           and asgn.effective_end_date
3884    and   asgn.assignment_type in ('E', 'C'); /* Bug 2777643 */
3885 
3886    cursor get_primary_assignment
3887    is
3888    select asgn.assignment_id
3889    from per_all_assignments_f asgn,
3890         (select person_id, actual_termination_date
3891            from per_periods_of_service
3892          union all
3893          select person_id, actual_termination_date
3894            from per_periods_of_placement) po -- FP M CWK
3895    where asgn.person_id            = p_person_id
3896    and   asgn.primary_flag         = 'Y'
3897    and   po.person_id              = p_person_id
3898    and   nvl(po.actual_termination_date, trunc(sysdate)) >= trunc(sysdate)
3899    and   asgn.person_id            = po.person_id
3900    -- and   po.period_of_service_id  = asgn.period_of_service_id
3901    and   p_start_date  between asgn.effective_start_date and asgn.effective_end_date
3902    and   asgn.assignment_type in ('E', 'C'); /* Bug 2777643 */
3903 
3904    cursor get_job_on_assignment
3905    is
3906    select asgn.job_id
3907    from per_all_assignments_f asgn,
3908         (select person_id, actual_termination_date
3909            from per_periods_of_service
3910          union all
3911          select person_id, actual_termination_date
3912            from per_periods_of_placement) po -- FP M CWK
3913    where asgn.person_id            = p_person_id
3914    and   asgn.primary_flag         = 'Y'
3915    and   po.person_id              = p_person_id
3916    and   nvl(po.actual_termination_date, trunc(sysdate)) >= trunc(sysdate)
3917    and   asgn.person_id            = po.person_id
3918    -- and   pos.period_of_service_id  = asgn.period_of_service_id
3919    and   asgn.job_id is not null
3920    and   p_start_date between asgn.effective_start_date
3921                           and asgn.effective_end_date
3922    and   asgn.assignment_type in ('E', 'C'); /* Bug 2777643 */
3923 
3924    cursor validate_resource is
3925    select person_id
3926    from   pa_resources_denorm
3927    where  person_id = p_person_id
3928    and    p_start_date between resource_effective_start_date
3929                            and resource_effective_end_date;
3930 
3931 
3932 BEGIN
3933    PA_DEBUG.set_err_stack('Validate_person');
3934 
3935   -------------------------------------------------------------------------
3936   --Cursor which checks if record exists in pa_resources_denorm
3937   --as of the p_Start_date
3938   -------------------------------------------------------------------------
3939   OPEN validate_resource;
3940   FETCH validate_resource into l_person_id;
3941   IF validate_resource%NOTFOUND THEN
3942       x_return_status := 'E';
3943   ELSE
3944       x_return_status := 'S';
3945   END IF;
3946   CLOSE validate_resource;
3947 
3948   IF x_return_status = 'S' THEN
3949       PA_DEBUG.Reset_Err_Stack;
3950       return;
3951   END IF;
3952 
3953   ------------------------------------------------------------
3954   --Logic which identifies the setup issue when a resource
3955   --record does not exist as of p_start_date
3956   ------------------------------------------------------------
3957 /* Bug#2683266 - Changed get_person_type cursor to validate_person_type in code below */
3958 
3959   OPEN validate_person_type;
3960   FETCH validate_person_type into l_person_type;
3961   IF validate_person_type%NOTFOUND THEN
3962      CLOSE validate_person_type;
3963      PA_UTILS.Add_Message( p_app_short_name  => 'PA'
3964                            ,p_msg_name       => 'PA_INVALID_PERSON_TYPE');
3965 
3966   ELSE
3967     CLOSE validate_person_type;
3968     OPEN get_active_assignment;
3969     FETCH get_active_assignment into l_assignment_id;
3970     IF get_active_assignment%NOTFOUND THEN
3971        CLOSE get_active_assignment;
3972        PA_UTILS.Add_Message( p_app_short_name  => 'PA'
3973                              ,p_msg_name       => 'PA_NO_ACTIVE_ASSIGNMENT');
3974     ELSE
3975       CLOSE get_active_assignment;
3976       OPEN get_primary_assignment;
3977       FETCH get_primary_assignment into l_assignment_id;
3978       IF get_primary_assignment%NOTFOUND THEN
3979          CLOSE get_primary_assignment;
3980          PA_UTILS.Add_Message( p_app_short_name  => 'PA'
3981                                ,p_msg_name       => 'PA_NO_PRIMARY_ASSIGNMENT');
3982       ELSE
3983         CLOSE get_primary_assignment;
3984         OPEN get_job_on_assignment;
3985         FETCH get_job_on_assignment into l_job_id;
3986         IF get_job_on_assignment%NOTFOUND THEN
3987            CLOSE get_job_on_assignment;
3988            PA_UTILS.Add_Message( p_app_short_name  => 'PA'
3989                                  ,p_msg_name       => 'PA_NO_JOB_ON_ASSIGNMENT');
3990         ELSE
3991            CLOSE get_job_on_assignment;
3992            PA_UTILS.Add_Message( p_app_short_name  => 'PA'
3993                                  ,p_msg_name       => 'PA_RS_INVALID_SETUP');
3994         END IF;
3995       END IF;
3996     END IF;
3997   END IF;
3998 
3999   PA_DEBUG.Reset_Err_Stack;
4000 
4001 EXCEPTION
4002 
4003     WHEN OTHERS THEN
4004      -- Set the exception Message and the stack
4005      FND_MSG_PUB.add_exc_msg(p_pkg_name       => 'PA_RESOURCE_UTILS.Validate_person'
4006                             ,p_procedure_name => PA_DEBUG.G_Err_Stack );
4007      x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
4008      RAISE;
4009 
4010 END validate_person;
4011 
4012 
4013 -- This function returns the party_id of a
4014 -- resource
4015 -- IN PARAMETER: p_resource_id
4016 FUNCTION get_party_id(p_resource_id IN NUMBER)
4017 RETURN NUMBER
4018 IS
4019 l_party_id NUMBER;
4020 BEGIN
4021 
4022    SELECT party_id
4023    INTO l_party_id
4024    FROM pa_resource_txn_attributes
4025    WHERE resource_id = p_resource_id;
4026 
4027    RETURN l_party_id;
4028 EXCEPTION
4029   WHEN OTHERS THEN
4030        RETURN -999;
4031 END get_party_id;
4032 
4033 -- This function returns the resource_type_code
4034 -- (i.e. EMPLOYEE or HZ_PARTY, etc) of a resource
4035 -- IN PARAMETER: p_resource_id
4036 FUNCTION get_resource_type(p_resource_id IN NUMBER)
4037 RETURN VARCHAR2
4038 IS
4039    l_resource_type  VARCHAR2(30);
4040 BEGIN
4041 
4042    SELECT resource_type_code
4043    INTO l_resource_type
4044    FROM pa_resources pr, pa_resource_types pt
4045    WHERE pr.resource_id = p_resource_id
4046      AND pr.resource_type_id = pt.resource_type_id;
4047 
4048    RETURN l_resource_type;
4049 EXCEPTION
4050   WHEN OTHERS THEN
4051        RETURN NULL;
4052 END get_resource_type;
4053 
4054 
4055 -- This function returns a lock handle for retrieving
4056 -- and releasing a dbms_lock.  We have made it as
4057 -- an autonomous transaction because it issues a commit.
4058 -- However, requesting and releasing a lock does not
4059 -- issue a commit;
4060 PROCEDURE allocate_unique(p_lock_name  IN VARCHAR2,
4061                           p_lock_handle OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
4062 IS
4063    PRAGMA AUTONOMOUS_TRANSACTION;
4064 BEGIN
4065      dbms_lock.allocate_unique(
4066          lockname => p_lock_name,
4067          lockhandle => p_lock_handle);
4068    commit;
4069 
4070 --4537865
4071 EXCEPTION
4072 WHEN OTHERS THEN
4073     p_lock_handle := NULL ;
4074     -- RAISE is not needed here . Caller takes care of this scenario by checking against p_lock_handle
4075 END allocate_unique;
4076 
4077 
4078 -- This function will set and acquire the user lock
4079 --
4080 -- Input parameters
4081 -- Parameter    Type       Required  Description
4082 -- p_source_id  NUMBER      Yes      Any unique id (person_id, resource_id, etc)
4083 -- p_lock_for   VARCHAR2    Yes      Any descriptive word to be used
4084 --                                   (e.g. Resource Pull)
4085 --
4086 -- Return Values
4087 --  0         Success
4088 -- Other      Unable to acquire lock
4089 
4090 
4091 FUNCTION Acquire_User_Lock ( p_source_id         IN  NUMBER,
4092                              p_lock_for          IN  VARCHAR2)
4093 
4094 RETURN NUMBER
4095 IS
4096      lock_status    NUMBER;
4097      lock_name      VARCHAR2(50);
4098      lockhndl       VARCHAR2(128);
4099      lock_mode      NUMBER:=6;
4100      lock_commitmode    BOOLEAN:=TRUE;
4101 BEGIN
4102 
4103     lock_name   := p_lock_for || '-' || p_source_id;
4104     IF ( p_source_id IS NULL ) THEN
4105       Return -99;
4106     END IF;
4107 
4108     /* Get lock handle for user lock */
4109     pa_resource_utils.allocate_unique(
4110             p_lock_name   =>lock_name,
4111             p_lock_handle =>lockhndl);
4112 
4113     IF ( lockhndl IS NOT NULL ) then
4114        /* Request the lock */
4115        lock_status := dbms_lock.request( lockhandle        => lockhndl,
4116                                          lockmode          => lock_mode,
4117                                          release_on_commit => lock_CommitMode,
4118                                          timeout           => 1);
4119 
4120        IF ( lock_status = 0 ) then  -- Got the lock
4121           Return 0;
4122        ELSE
4123           Return (-1*lock_status);
4124           -- Return the status obtained on request
4125        END IF;
4126 
4127     ELSE
4128           Return -99;  -- Failed to allocate lock
4129     END IF;
4130 
4131     RETURN(lock_status);
4132 
4133 END  Acquire_User_Lock;
4134 
4135 
4136 -- This procedure will release user lock
4137 --
4138 -- Input parameters
4139 -- Parameter    Type       Required            Description
4140 -- p_source_id  NUMBER      Yes      Any unique id (person_id, resource_id, etc)
4141 -- p_lock_for   VARCHAR2    Yes      Any descriptive word to be used
4142 --                                   (e.g. Resource Pull)
4143 --
4144 -- Return Values
4145 --  0         Success
4146 -- Other      Unable to acquire lock
4147 
4148 FUNCTION Release_User_Lock (p_source_id   IN  NUMBER,
4149                             p_lock_for    IN  VARCHAR2)
4150  RETURN NUMBER
4151  IS
4152      lock_status   number;
4153      lock_name     VARCHAR2(50);
4154      lockhndl      VARCHAR2(128);
4155 BEGIN
4156 
4157     lock_name   := p_lock_for || '-' || p_source_id;
4158     IF ( p_source_id IS NULL ) THEN
4159       Return -99;
4160     END IF;
4161 
4162     /* Get lock handle for user lock */
4163     pa_resource_utils.allocate_unique(
4164             p_lock_name   =>lock_name,
4165             p_lock_handle =>lockhndl);
4166 
4167     IF ( lockhndl IS NOT NULL ) then
4168           lock_status := dbms_lock.release(lockhandle =>lockhndl);
4169 
4170           IF ( lock_status = 0 ) then  -- Got the lock
4171                 Return 0;
4172           ELSE
4173                 Return (-1*lock_status);
4174                 -- Return the status obtained on request
4175           END IF;
4176     ELSE
4177           Return -99;  -- Failed to allocate lock
4178     END IF;
4179 
4180     RETURN(lock_status);
4181 
4182 END Release_User_Lock;
4183 
4184 
4185 --  PROCEDURE
4186 --             get_resource_id
4187 --  PURPOSE
4188 --             This function returns the resource_id of the
4189 --             person using the fnd user name or user ID passed to the
4190 --             function
4191 FUNCTION get_resource_id(p_user_name IN VARCHAR2 DEFAULT NULL,
4192                          p_user_id   IN NUMBER   DEFAULT NULL)
4193   RETURN NUMBER
4194   IS
4195       l_emp_id NUMBER;
4196       l_cust_id NUMBER;
4197       l_res_id NUMBER;
4198 BEGIN
4199       IF (p_user_name IS NULL) AND (p_user_id IS NULL) THEN
4200          RETURN -999;
4201       END IF;
4202 
4203       -- 4586987 customer_id is changed to person_party_id
4204       /*
4205       SELECT employee_id, customer_id
4206       INTO   l_emp_id, l_cust_id
4207       FROM   fnd_user
4208       WHERE  user_name = nvl(p_user_name, user_name)
4209       AND    user_id = nvl(p_user_id, user_id);
4210       */
4211 
4212       /* rewrite it for perf bug 4887375
4213       SELECT employee_id,person_party_id
4214       INTO l_emp_id,l_cust_id
4215       FROM fnd_user
4216       WHERE user_name = nvl(p_user_name,user_name)
4217       AND user_id =nvl(p_user_id,user_id);*/
4218 
4219       IF p_user_name IS NULL THEN
4220         SELECT employee_id, person_party_id
4221         INTO   l_emp_id, l_cust_id
4222         FROM   fnd_user
4223         WHERE  user_id = p_user_id;
4224       ELSIF p_user_id IS NULL THEN
4225         SELECT employee_id, person_party_id
4226         INTO   l_emp_id, l_cust_id
4227         FROM   fnd_user
4228         WHERE  user_name = p_user_name;
4229       ELSE
4230         SELECT employee_id, person_party_id
4231         INTO   l_emp_id, l_cust_id
4232         FROM   fnd_user
4233         WHERE  user_name = p_user_name
4234         AND user_id = p_user_id;
4235       END IF;
4236 
4237       -- 4586987 end
4238 
4239       IF l_emp_id IS NOT NULL THEN
4240          RETURN get_resource_id(p_person_id => l_emp_id);
4241       ELSIF l_cust_id IS NOT NULL THEN
4242          SELECT resource_id
4243          INTO l_res_id
4244          FROM pa_resource_txn_attributes
4245          WHERE party_id = l_cust_id;
4246 
4247          RETURN l_res_id;
4248       END IF;
4249 
4250       RETURN -999;
4251 
4252 EXCEPTION
4253       WHEN OTHERS THEN
4254           RETURN -999;
4255 END get_resource_id;
4256 
4257 --  PROCEDURE
4258 --             get_res_name_from_type
4259 --  PURPOSE
4260 --             This function returns the name of the
4261 --             person using the resource type to determine whether
4262 --             it is an HR or HZ resource.
4263 FUNCTION get_res_name_from_type(p_resource_type_id     IN NUMBER,
4264                                 p_resource_source_id   IN NUMBER)
4265 RETURN VARCHAR2 IS
4266 
4267 l_resource_type_code pa_resource_types.resource_type_code%TYPE;
4268 l_name pa_resources.name%TYPE;
4269 
4270 BEGIN
4271 
4272       BEGIN
4273 
4274          SELECT resource_type_code
4275          INTO l_resource_type_code
4276          FROM pa_resource_types
4277          WHERE resource_type_id = p_resource_type_id;
4278 
4279          EXCEPTION
4280             WHEN OTHERS THEN
4281             RETURN NULL;
4282       END;
4283 
4284       IF l_resource_type_code = 'EMPLOYEE' THEN
4285 
4286          SELECT hzp.party_name
4287          INTO l_name
4288          FROM per_all_people_f peo, hz_parties hzp
4289          WHERE peo.person_id = p_resource_source_id
4290          AND   sysdate BETWEEN peo.effective_start_date AND
4291                                peo.effective_end_date
4292          AND   peo.party_id = hzp.party_id;
4293 
4294          RETURN l_name;
4295 
4296       ELSIF l_resource_type_code = 'HZ_PARTY' THEN
4297 
4298          SELECT hzp.party_name
4299          INTO l_name
4300          FROM hz_parties hzp
4301          WHERE hzp.party_id = p_resource_source_id;
4302 
4303          RETURN l_name;
4304 
4305      ELSE
4306          RETURN NULL;
4307 
4308      END IF;
4309 
4310 EXCEPTION
4311       WHEN OTHERS THEN
4312          RETURN NULL;
4313 
4314 END get_res_name_from_type;
4315 
4316 --  PROCEDURE
4317 --             get_resource_name
4318 --  PURPOSE
4319 --             This function returns the resource_name of the
4320 --             resource_id passed in using pa_resources table
4321 FUNCTION get_resource_name(p_resource_id IN NUMBER)
4322   RETURN VARCHAR2
4323   IS
4324       l_name pa_resources.name%TYPE;
4325 BEGIN
4326       SELECT name
4327       INTO l_name
4328       FROM pa_resources
4329       WHERE resource_id = p_resource_id;
4330 
4331       RETURN l_name;
4332 EXCEPTION
4333       WHEN OTHERS THEN
4334          RETURN NULL;
4335 END get_resource_name;
4336 
4337 --  FUNCTION
4338 --              get_pa_logged_resp
4339 --  PURPOSE
4340 --              This procedure checks if logged responsibility is
4341 --              Project Super User or Resource Manager
4342 --              or Staffing Manager
4343 --
4344 --  HISTORY
4345 --              25-SEP-2001  created  virangan
4346 --
4347 FUNCTION get_pa_logged_resp
4348     RETURN VARCHAR2
4349 IS
4350 
4351     l_menu_name varchar2(255);
4352     l_pa_logged_resp varchar2(2) := 'TM';
4353     l_function_id number;
4354     l_menu_id number;
4355 
4356 BEGIN
4357    /* resp.application_id = fnd_global.resp_appl_id join is added for Perfomance
4358         Bug 2634995        */
4359     select menu_name, resp.menu_id
4360     into   l_menu_name, l_menu_id
4361     from   fnd_menus menu,
4362            fnd_responsibility resp
4363     where  resp.responsibility_id = fnd_global.resp_id
4364     and    resp.menu_id           = menu.menu_id
4365     and    resp.application_id    = fnd_global.resp_appl_id ;
4366 
4367     select function_id
4368     into l_function_id
4369     from fnd_form_functions
4370     where function_name='PA_RES_LIST';
4371 
4372     /* changed for bug 2775111: recently the function 'PA_STAFF_HOME_RM'
4373        got moved from menu 'PA_PRM_RES_MGR' to 'PA_STAFFING_RES_MGR'.
4374        Since FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS doesn't work recursively,
4375        we needed use new submenu to tell the login resp of resource manager.
4376      if FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
4377            menu_name          => l_menu_name,
4378            sub_menu_name      => '',
4379            function_name      => 'PA_STAFF_HOME_RM')  */
4380 
4381     if FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
4382            menu_name          => l_menu_name,
4383            sub_menu_name      => 'PA_STAFFING_RES_MGR',
4384            function_name      => '')
4385     then
4386            l_pa_logged_resp := 'RM';
4387 
4388     elsif FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
4389            menu_name          => l_menu_name,
4390            sub_menu_name      => '',
4391            function_name      => 'PA_STAFF_HOME')
4392     then
4393            l_pa_logged_resp := 'SM';
4394  /* Updated following code since the menu got changed and
4395     'PA_RES_LIST' is not loger direct under the main menu.
4396     elsif FND_FUNCTION_SECURITY.MENU_ENTRY_EXISTS(
4397            menu_name          => l_menu_name,
4398            sub_menu_name      => '',
4399            function_name      => 'PA_RES_LIST') */
4400     elsif FND_FUNCTION.Is_function_on_menu (
4401           p_menu_id       => l_menu_id,
4402           p_function_id       => l_function_id )
4403     then
4404            l_pa_logged_resp := 'SU';
4405     end if;
4406 
4407     return l_pa_logged_resp;
4408 
4409 EXCEPTION
4410     WHEN NO_DATA_FOUND THEN
4411         RETURN 'SU';
4412     WHEN OTHERS THEN
4413         RETURN null;
4414 
4415 END get_pa_logged_resp;
4416 
4417 
4418 --  PROCEDURE
4419 --             get_person_id_name
4420 --  PURPOSE
4421 --             This procedure gives the person_name and person_id
4422 --             based on person_name with a wildcard character '%'.
4423 --             Will only return one row (even if more exists) and uses like comparison.
4424 --             This is used by Check_ManagerName_Or_Id when the p_check=Y.
4425 --             Currently, p_check is Y only when it comes from My Resources
4426 --             page.
4427 --  HISTORY
4428 --             25-JUL-2002  Created    adabdull
4429 --+
4430 PROCEDURE get_person_id_name ( p_person_name IN  VARCHAR2
4431                               ,x_person_id   OUT NOCOPY NUMBER --File.Sql.39 bug 4440895
4432                               ,x_person_name OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
4433 IS
4434 BEGIN
4435 
4436      SELECT person_id, resource_name
4437      INTO x_person_id, x_person_name
4438      FROM pa_resources_denorm
4439      WHERE resource_name like p_person_name
4440        AND rownum=1;
4441 
4442 EXCEPTION
4443     WHEN OTHERS THEN
4444         x_person_id   := NULL;
4445         x_person_name := NULL;
4446 END get_person_id_name;
4447 
4448 
4449 --  PROCEDURE
4450 --             Check_ManagerName_Or_Id
4451 --  PURPOSE
4452 --             Specifically for resource supervisor hierarchy use.
4453 --             This procedure validates the manager_id and manager_name passed.
4454 --             It also depends on the responsibility value. User needs to pass
4455 --             RM if resource manager because it uses another view to validate
4456 --             the manager (whether the manager belongs to the login user
4457 --             HR supervisor hierarchy).
4458 --  HISTORY
4459 --             20-AUG-2002  Created    adabdull
4460 --+
4461 PROCEDURE Check_ManagerName_Or_Id(
4462                             p_manager_name       IN  VARCHAR2
4463                            ,p_manager_id         IN  NUMBER
4464                            ,p_responsibility     IN  VARCHAR2
4465                            ,p_check              IN  VARCHAR2
4466                            ,x_manager_id         OUT NOCOPY NUMBER --File.Sql.39 bug 4440895
4467                            ,x_msg_count          OUT NOCOPY NUMBER --File.Sql.39 bug 4440895
4468                            ,x_return_status      OUT NOCOPY VARCHAR2 --File.Sql.39 bug 4440895
4469                            ,x_error_message_code OUT NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
4470 IS
4471      l_manager_name   PA_RESOURCES_DENORM.RESOURCE_NAME%TYPE;
4472      l_manager_id     NUMBER;
4473 BEGIN
4474 
4475      -- this comes from My Resources page because the manager_name passed
4476      -- here can contain '%'. So we need to get the 'real' person_name and
4477      -- person_id
4478      IF p_check = 'Y' THEN
4479           Get_Person_Id_Name ( p_person_name => p_manager_name
4480                               ,x_person_id   => l_manager_id
4481                               ,x_person_name => l_manager_name);
4482      ELSE
4483           l_manager_name := p_manager_name;
4484           l_manager_id   := p_manager_id;
4485      END IF;
4486 
4487 
4488      -- Do not use the manager_id in the select statements if it is null.
4489      -- Case when user just entered the name, without using LOV
4490      IF l_manager_id IS NULL THEN
4491          --dbms_output.put_line('Manager Id is null');
4492 
4493          -- p_responsibility = RM
4494          -- Validates using pa_rep_res_mgr_v when the user's responsibility
4495          -- is Resource Manager
4496          IF p_responsibility = 'RM' THEN
4497              -- Changes for bug 3616010 - added hint and removed use
4498              -- of view for performance
4499              select /* +index PA_RESOURCES_DENORM PA_RESOURCES_DENORM_N2 */
4500                     manager_id into x_manager_id
4501              from pa_resources_denorm --pa_rep_res_mgr_v
4502              where manager_name = l_manager_name
4503              and rownum = 1; -- to stop multiple rows error
4504              --dbms_output.put_line('mgr id RM - id null ' || x_manager_id);
4505 
4506          ELSE
4507          -- Validates using pa_managers_v when the user's responsibility is
4508          -- Super User or Staffing Manager
4509              select distinct manager_id into x_manager_id
4510              from pa_managers_v
4511              where manager_full_name = l_manager_name;
4512              --dbms_output.put_line('mgr id M - id null ' || x_manager_id);
4513          END IF;
4514 
4515      ELSE
4516          --dbms_output.put_line('Manager Id is NOT null');
4517          -- do a similar check as above, except also use manager_id to
4518          -- refine the search better (this is the case, when user uses the
4519          -- LOV to select the manager)
4520          IF p_responsibility = 'RM' THEN
4521              -- Changes for bug 3616010 - removed use
4522              -- of view for performance
4523              select manager_id into x_manager_id
4524              from pa_resources_denorm --pa_rep_res_mgr_v
4525              where manager_name = l_manager_name
4526                and manager_id   = l_manager_id
4527                and rownum = 1;
4528              --dbms_output.put_line('mgr id RM - id not null ' || x_manager_id);
4529          ELSE
4530              select distinct manager_id into x_manager_id
4531              from pa_managers_v
4532              where manager_full_name = l_manager_name
4533                and manager_id        = l_manager_id;
4534              --dbms_output.put_line('mgr id M - id not null ' || x_manager_id);
4535          END IF;
4536      END IF;
4537 
4538      x_return_status := FND_API.G_RET_STS_SUCCESS;
4539      x_msg_count     := FND_MSG_PUB.Count_Msg;
4540 
4541 EXCEPTION
4542    WHEN NO_DATA_FOUND THEN
4543       x_manager_id := NULL;
4544       x_return_status := FND_API.G_RET_STS_ERROR;
4545       x_error_message_code := 'PA_RES_INVALID_MGR_HIER';
4546       x_msg_count     := FND_MSG_PUB.Count_Msg;
4547 
4548    WHEN TOO_MANY_ROWS THEN
4549       x_manager_id := NULL;
4550       x_return_status := FND_API.G_RET_STS_ERROR;
4551       x_error_message_code := 'PA_MULTIPLE_RESOURCE';
4552       x_msg_count     := FND_MSG_PUB.Count_Msg;
4553 
4554    WHEN OTHERS THEN
4555       x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
4556       x_manager_id := NULL;
4557       x_msg_count     := FND_MSG_PUB.Count_Msg;
4558 
4559 END Check_ManagerName_Or_Id;
4560 
4561 
4562 --  FUNCTION
4563 --              get_person_name_no_date
4564 --  PURPOSE
4565 --              This function returns the latest person name not
4566 --              based on any date.
4567 --
4568 --  HISTORY
4569 --  28-APR-2003   shyugen
4570 
4571 FUNCTION get_person_name_no_date(p_person_id IN NUMBER) RETURN VARCHAR IS
4572 
4573  l_person_name PER_all_PEOPLE_F.FULL_NAME%TYPE := null;
4574 
4575 BEGIN
4576 
4577  IF p_person_id IS NOT NULL THEN
4578 
4579    SELECT full_name
4580      INTO l_person_name
4581      FROM per_all_people_f
4582     WHERE person_id = p_person_id
4583       AND effective_end_date = (SELECT MAX(effective_end_date)
4584                                   FROM per_all_people_f
4585                                  WHERE person_id = p_person_id);
4586  END IF;
4587 
4588  RETURN l_person_name;
4589 
4590 EXCEPTION
4591  WHEN OTHERS THEN
4592    RETURN null;
4593 
4594 END get_person_name_no_date;
4595 
4596 --  FUNCTION
4597 --              get_projected_end_date
4598 --  PURPOSE
4599 --              This function returns the projected end date for a
4600 --              contingent worker.
4601 --
4602 --  HISTORY
4603 --  15-APR-2004   ramurthy
4604 
4605 
4606 FUNCTION get_projected_end_date(p_person_id IN NUMBER) RETURN DATE IS
4607 
4608 l_term_date DATE;
4609 
4610 BEGIN
4611 
4612  IF p_person_id IS NOT NULL THEN
4613 
4614    SELECT NVL(pp.projected_termination_date, asg.projected_assignment_end)	-- Bug#14594489
4615      INTO l_term_date
4616      FROM per_all_assignments_f asg,
4617           per_periods_of_placement pp
4618     WHERE asg.person_id = p_person_id
4619       AND pp.person_id = p_person_id
4620       AND asg.primary_flag = 'Y'
4621       AND asg.assignment_type = 'C'
4622       AND asg.period_of_placement_date_start = pp.date_start
4623       AND trunc(SYSDATE) BETWEEN trunc(asg.effective_start_date)
4624                              AND trunc(asg.effective_end_date);
4625 
4626  END IF;
4627 
4628  RETURN l_term_date;
4629 
4630 EXCEPTION
4631  WHEN OTHERS THEN
4632    RETURN null;
4633 
4634 END get_projected_end_date;
4635 
4636  /*bug 3737529 - Code addition starts
4637  Added the function get_hr_manager_id for this 3737529*/
4638 
4639 FUNCTION get_hr_manager_id(p_resource_id IN NUMBER,
4640                            p_start_date IN  DATE DEFAULT NULL) --Bug 4473484
4641                RETURN NUMBER
4642 IS
4643 
4644  x_ManagerId PER_PEOPLE_F.PERSON_ID%TYPE := null;
4645  l_manager_start_date DATE := null;
4646  v_return_status VARCHAR2(1);
4647  v_personid NUMBER;
4648  v_error_message_code    fnd_new_messages.message_name%TYPE;
4649  l_start_date DATE;
4650  x_ManagerName  PER_all_PEOPLE_F.FULL_NAME%TYPE :=null;
4651 
4652 
4653 BEGIN
4654 
4655        -- initialize the return status to success
4656            v_return_status := FND_API.G_RET_STS_SUCCESS;
4657 
4658 --Bug 4473484
4659       IF p_start_date IS NULL THEN
4660           l_start_date := sysdate;
4661       ELSE
4662           l_start_date := p_start_date;
4663       END IF;
4664 /*      IF p_assignment_id IS NULL THEN
4665                   l_start_date := sysdate;
4666       ELSE
4667                   --Get the assignment start date
4668            BEGIN
4669                   SELECT start_date
4670                   INTO   l_start_date
4671                   FROM   pa_project_assignments
4672                   WHERE  assignment_id = p_assignment_id
4673                   ;
4674            EXCEPTION
4675                           WHEN OTHERS THEN
4676                 l_start_date := sysdate;
4677                    END;
4678        END IF; */
4679 
4680          get_person_id(p_resource_id
4681                      ,v_personid
4682                      ,v_error_message_code
4683                      ,v_return_status);
4684         --check for return status if error found then add it to stack
4685         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
4686            PA_UTILS.add_message(p_app_short_name => 'PA',
4687                                 p_msg_name => v_error_message_code);
4688         END IF;
4689 
4690 if l_start_date > sysdate then
4691    l_start_date := l_start_date;
4692 elsif l_start_date < sysdate then
4693    l_start_date := sysdate;
4694 end if;
4695 
4696 WHILE (l_manager_start_date is NULL) LOOP
4697        -- get manager name and id
4698        get_manager_id_name(v_personid
4699                           ,l_start_date
4700                           ,x_ManagerId
4701                           ,x_ManagerName
4702                           ,v_error_message_code
4703                           ,v_return_status);
4704         IF v_return_status =  FND_API.G_RET_STS_ERROR THEN
4705            PA_UTILS.add_message(p_app_short_name => 'PA',
4706                                 p_msg_name => v_error_message_code);
4707         END IF;
4708         IF x_ManagerId IS NULL  THEN
4709      x_ManagerName := null;
4710           l_manager_start_date := trunc(sysdate);
4711         ELSE
4712 
4713                 BEGIN
4714                         select effective_start_date into l_manager_start_date from pa_employees
4715                         where person_id=x_ManagerId
4716                         and active='*';
4717                 EXCEPTION
4718                         WHEN NO_DATA_FOUND then
4719                         l_manager_start_date := NULL;
4720                         v_personid := x_ManagerId;
4721                         x_ManagerId := null;
4722                         x_ManagerName:= null;
4723                 END;
4724         END IF;
4725 END LOOP;
4726 
4727 PA_RESOURCE_UTILS.G_HR_SUPERVISOR_NAME := x_ManagerName;
4728 PA_RESOURCE_UTILS.G_HR_SUPERVISOR_ID := x_ManagerId;
4729 -- PA_RESOURCE_UTILS.G_ASSIGNMENT_ID := p_assignment_id; -- Bug 4473484
4730 PA_RESOURCE_UTILS.G_START_DATE := p_start_date;  -- Bug 4473484
4731 PA_RESOURCE_UTILS.G_RESOURCE_ID := p_resource_id;
4732 
4733 RETURN x_ManagerId;
4734 
4735 END get_hr_manager_id;
4736 
4737 FUNCTION get_hr_manager_name(p_resource_id IN NUMBER,p_start_date IN  DATE DEFAULT NULL) RETURN VARCHAR2  -- Bug 4473484
4738 IS
4739 l_supervisor NUMBER;
4740 BEGIN
4741  IF PA_RESOURCE_UTILS.G_RESOURCE_ID = p_resource_id and PA_RESOURCE_UTILS.G_START_DATE = p_start_date THEN -- Bug 4473484
4742    null;
4743  ELSE
4744    l_supervisor := get_hr_manager_id(p_resource_id => p_resource_id, p_start_date => p_start_date); -- Bug 4473484
4745  END IF;
4746    RETURN PA_RESOURCE_UTILS.G_HR_SUPERVISOR_NAME;
4747 
4748 END get_hr_manager_name;
4749 
4750 /*Bug 3737529: Code Addition ends*/
4751 
4752 /* *******************************************************************
4753  * This function checks to see if the given supplier ID is used by any
4754  * planning resource lists or resource breakdown structures.  If it is
4755  * in use, it returns 'Y'; if not, it returns 'N'
4756  * ******************************************************************* */
4757 FUNCTION chk_supplier_in_use(p_supplier_id IN NUMBER)
4758 RETURN VARCHAR2 IS
4759 
4760 l_in_use VARCHAR2(1) := 'N';
4761 
4762 BEGIN
4763 
4764    BEGIN
4765    SELECT 'Y'
4766    INTO   l_in_use
4767    FROM   DUAL
4768    WHERE  EXISTS (SELECT 'Y'
4769                   FROM   pa_resource_list_members
4770                   WHERE  vendor_id = p_supplier_id
4771                   UNION ALL
4772                   SELECT 'Y'
4773                   FROM   pa_rbs_elements
4774                   WHERE  supplier_id = p_supplier_id);
4775 
4776    EXCEPTION WHEN NO_DATA_FOUND THEN
4777       l_in_use := 'N';
4778    END;
4779 
4780 RETURN l_in_use;
4781 
4782 END chk_supplier_in_use;
4783 
4784 --
4785 --  FUNCTION
4786 --              get_term_type
4787 --  PURPOSE
4788 --              This function returns the leaving/termination reason type
4789 --              of an employee/contingent worker as 'V' or 'I'
4790 --  HISTORY
4791 --   05-MAR-207       kjai       Created for Bug 5683340
4792 --
4793 FUNCTION get_term_type( p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE )
4794 RETURN VARCHAR2
4795 IS
4796 
4797 l_formula_id          NUMBER;
4798 l_term_type           VARCHAR2(1);
4799 l_resource_person_type PA_RESOURCES_DENORM.RESOURCE_PERSON_TYPE%TYPE ;
4800 
4801 l_leav_reas PER_PERIODS_OF_SERVICE.LEAVING_REASON%TYPE ;
4802 l_term_reas PER_PERIODS_OF_PLACEMENT.TERMINATION_REASON%TYPE ;
4803 
4804 CURSOR c_formula
4805 IS
4806    SELECT formula_id
4807    FROM   ff_formulas_f
4808    --WHERE  business_group_id+0 = 0  -- commented as part of bug 7613549
4809    WHERE  nvl(business_group_id,0) = 0 -- added as part of bug 7613549
4810    AND    SYSDATE BETWEEN effective_start_date AND effective_end_date
4811    AND    formula_name = 'HR_PA_MOVE'
4812    AND    formula_type_id
4813                = HR_PERSON_FLEX_LOGIC.GetFormulaTypeID('Oracle Payroll');
4814 
4815 CURSOR c_leav_reas (c_person_id PA_EMPLOYEES.PERSON_ID%TYPE)
4816 IS
4817 SELECT leaving_reason
4818 FROM (SELECT leaving_reason
4819       FROM per_periods_of_service
4820       WHERE person_id = c_person_id
4821       AND actual_termination_date IS NOT NULL
4822       ORDER BY actual_termination_date DESC)
4823 WHERE ROWNUM = 1;
4824 
4825 CURSOR c_term_reas (c_person_id PA_EMPLOYEES.PERSON_ID%TYPE)
4826 IS
4827 SELECT termination_reason
4828 FROM (SELECT termination_reason
4829       FROM per_periods_of_placement
4830       WHERE person_id = c_person_id
4831       AND actual_termination_date IS NOT NULL
4832       ORDER BY actual_termination_date DESC)
4833 WHERE ROWNUM = 1;
4834 
4835 -- Bug 7588937
4836 CURSOR c_res_person_type (c_person_id PA_EMPLOYEES.PERSON_ID%TYPE)
4837 IS
4838 SELECT  distinct(resource_person_type)
4839 FROM    pa_resources_denorm
4840 WHERE   person_id = c_person_id;
4841 
4842 BEGIN
4843 
4844  OPEN  c_formula;
4845  FETCH c_formula INTO l_formula_id;
4846  IF (c_formula%NOTFOUND OR c_formula%NOTFOUND IS NULL) THEN
4847 
4848     CLOSE c_formula;
4849     l_term_type := 'V';
4850 
4851  ELSE
4852 
4853     -- Start Changes for Bug 7588937
4854 
4855     /*SELECT  distinct(resource_person_type)
4856     INTO    l_resource_person_type
4857     FROM    pa_resources_denorm
4858     WHERE   person_id = p_person_id;*/
4859 
4860     OPEN c_res_person_type(p_person_id);
4861     FETCH c_res_person_type INTO l_resource_person_type;
4862     IF c_res_person_type%NOTFOUND THEN
4863       --CLOSE c_res_person_type;
4864       l_term_type := 'V';
4865     END IF;
4866 
4867     IF ( l_resource_person_type is NULL or l_resource_person_type = '') THEN
4868       l_term_type := 'V';
4869     END IF;
4870 
4871     CLOSE c_res_person_type;
4872 
4873     -- End of changes for Bug 7588937
4874 
4875     IF ( l_resource_person_type = 'EMP') THEN
4876 
4877       OPEN c_leav_reas(p_person_id);
4878       FETCH c_leav_reas INTO l_leav_reas;
4879       IF c_leav_reas%FOUND THEN
4880         CLOSE c_leav_reas;
4881         l_term_type := HR_PERSON_FLEX_LOGIC.GetTermType(p_term_formula_id	=> l_formula_id
4882                                                              ,p_leaving_reason => l_leav_reas
4883                                                              ,p_session_date => sysdate);
4884       ELSE
4885         CLOSE c_leav_reas;
4886         l_term_type := 'V';
4887       END IF ; --IF c_leav_reas%FOUND
4888 
4889     ELSIF (l_resource_person_type = 'CWK' ) THEN
4890 
4891       OPEN c_term_reas(p_person_id);
4892       FETCH c_term_reas INTO l_term_reas;
4893       IF c_term_reas%FOUND THEN
4894         CLOSE c_term_reas;
4895         l_term_type := HR_PERSON_FLEX_LOGIC.GetTermType(p_term_formula_id	=> l_formula_id
4896                                                              ,p_leaving_reason => l_term_reas
4897                                                              ,p_session_date => sysdate);
4898       ELSE
4899         CLOSE c_term_reas;
4900         l_term_type := 'V';
4901       END IF ; --IF c_term_reas%FOUND
4902 
4903     END IF ;  --IF (l_system_person_type = 'EMP' )
4904 
4905     CLOSE c_formula;
4906 
4907  END IF ;  --IF (c_formula%NOTFOUND OR c_formula%NOTFOUND IS NULL)
4908 
4909  RETURN l_term_type ;
4910 
4911 END get_term_type;
4912 
4913 --
4914 --  PROCEDURE
4915 --              Init_FTE_Sync_WF
4916 --  PURPOSE
4917 --              This procedure is used to initiate Timeout_termination_process
4918 --              workflow for future termination of employee.
4919 --  HISTORY
4920 --   05-MAR-207       kjai       Created for Bug 5683340
4921 --
4922 PROCEDURE Init_FTE_Sync_WF( p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE,
4923                             x_invol_term        OUT NOCOPY VARCHAR2,
4924 			    x_return_status  OUT NOCOPY VARCHAR2,
4925 			    x_msg_data       OUT NOCOPY VARCHAR2,
4926 			    x_msg_count      OUT NOCOPY NUMBER
4927 			    )
4928  IS
4929 
4930      l_term_type  VARCHAR2(1);
4931      l_invol_term VARCHAR2(1);
4932      l_return_end_date DATE;
4933      l_wait_days NUMBER;
4934 
4935      l_resource_effective_end_date DATE ;
4936      l_future_term_wf_flag pa_resources.future_term_wf_flag%TYPE ;
4937 
4938      l_msg_index_out NUMBER;
4939 
4940 BEGIN
4941 
4942      -- initialize the error stack
4943      PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.Init_FTE_Sync_WF');
4944      -- initialize the return  status to success
4945      x_return_status := FND_API.G_RET_STS_SUCCESS;
4946 
4947      l_term_type := pa_resource_utils.get_term_type(p_person_id) ;
4948 
4949 	IF (l_term_type = 'I') THEN
4950 
4951             IF( p_person_id <> nvl(G_TERM_PERSON_ID, -999) ) THEN
4952 
4953                 G_TERM_PERSON_ID := p_person_id ;
4954 
4955 	        pa_resource_utils.is_fte(p_person_id => G_TERM_PERSON_ID,
4956 	                                 x_return_end_date => l_return_end_date,
4957 					 x_invol_term => l_invol_term ,
4958 	                                 x_wait_days => l_wait_days ,
4959 					 x_msg_data => x_msg_data,
4960 					 x_msg_count => x_msg_count,
4961                                          x_return_status => x_return_status );
4962 
4963 		G_FTE_FLAG := l_invol_term;
4964                 G_FTE_DATE := l_return_end_date ;
4965 
4966 	    END IF ; --IF( l_person_id <> G_PERSON_ID )
4967 
4968 
4969 	    IF (NVL(G_FTE_FLAG,'N') = 'Y') THEN
4970 
4971                 SELECT max(resource_effective_end_date)
4972 		INTO l_resource_effective_end_date
4973 		FROM pa_resources_denorm
4974                 WHERE person_id = G_TERM_PERSON_ID; --l_person_id
4975 
4976 		UPDATE pa_resources_denorm
4977 		SET resource_effective_end_date = G_FTE_DATE,
4978                 last_update_date      = sysdate,
4979                 last_updated_by       = fnd_global.user_id,
4980                 last_update_login     = fnd_global.login_id
4981 		WHERE person_id = G_TERM_PERSON_ID --l_person_id
4982 		AND resource_effective_end_date = l_resource_effective_end_date;
4983 
4984                 pa_resource_utils.get_fte_flag(p_person_id => G_TERM_PERSON_ID,
4985 		                               x_future_term_wf_flag => l_future_term_wf_flag,
4986                                                x_msg_data => x_msg_data,
4987                                                x_msg_count => x_msg_count,
4988                                                x_return_status => x_return_status);
4989 
4990                 IF l_future_term_wf_flag IS NULL THEN
4991 
4992 		   PA_HR_UPDATE_PA_ENTITIES.create_fte_sync_wf(p_person_id => G_TERM_PERSON_ID,
4993 		                                               p_wait_days => l_wait_days,
4994 		                                               x_return_status => x_return_status,
4995 							       x_msg_count => x_msg_count,
4996 							       x_msg_data => x_msg_data);
4997 
4998 
4999                    pa_resource_utils.set_fte_flag(p_person_id  => G_TERM_PERSON_ID,
5000                                                   p_future_term_wf_flag => 'Y',
5001 						  x_msg_data => x_msg_data,
5002                                                   x_msg_count => x_msg_count,
5003                                                   x_return_status => x_return_status  ) ;
5004 
5005 		   l_invol_term  := 'Y';
5006 
5007 
5008                 ELSE -- IF l_future_term_wf_flag IS NULL
5009 
5010 		   l_invol_term  := 'Y';
5011 
5012 		END IF ; --IF l_future_term_wf_flag IS NULL
5013 
5014 	    ELSE -- IF (G_FTE_FLAG = 'Y')
5015 
5016 	       pa_resource_utils.set_fte_flag(p_person_id  => G_TERM_PERSON_ID,
5017                                               p_future_term_wf_flag => NULL,
5018 					      x_msg_data => x_msg_data,
5019                                               x_msg_count => x_msg_count,
5020                                               x_return_status => x_return_status) ;
5021 
5022                l_invol_term := 'N';
5023 
5024 	    END IF ; --IF (G_FTE_FLAG = 'Y')
5025 
5026 
5027 	ELSE   --IF (l_term_type = 'I')
5028 
5029 	 l_invol_term := 'N';
5030 
5031 	 /* Added for Bug 6056112 */
5032 	 pa_resource_utils.set_fte_flag(p_person_id  => p_person_id,
5033                                   p_future_term_wf_flag => NULL,
5034                                   x_msg_data => x_msg_data,
5035                                   x_msg_count => x_msg_count,
5036                                   x_return_status => x_return_status) ;
5037 
5038 	END IF ; --IF (l_term_type = 'I')
5039 
5040 
5041     x_invol_term := l_invol_term ;
5042 
5043     -- reset the error stack
5044     PA_DEBUG.reset_err_stack;
5045 
5046 
5047 EXCEPTION
5048      WHEN OTHERS THEN
5049      x_return_status := FND_API.G_RET_STS_ERROR;
5050      x_msg_count := 1;
5051      x_msg_data  := substr(SQLERRM,1,240);
5052      FND_MSG_PUB.add_exc_msg( p_pkg_name => 'PA_RESOURCE_UTILS',
5053        p_procedure_name   => 'Init_FTE_sync_wf');
5054        If x_msg_count = 1 THEN
5055           pa_interface_utils_pub.get_messages
5056             (p_encoded        => FND_API.G_TRUE,
5057              p_msg_index      => 1,
5058              p_msg_count      => x_msg_count,
5059              p_msg_data       => x_msg_data,
5060              p_data           => x_msg_data,
5061              p_msg_index_out  => l_msg_index_out );
5062        End If;
5063      raise;
5064 END Init_FTE_Sync_WF;
5065 
5066 
5067 --
5068 --  PROCEDURE
5069 --              set_fte_flag
5070 --  PURPOSE
5071 --              This procedure sets the new future_term_wf_flag
5072 --              in table pa_resources for the passed person_id
5073 --  HISTORY
5074 --  05-MAR-207       kjai       Created for Bug 5683340
5075 --
5076 PROCEDURE set_fte_flag(p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE,
5077                        p_future_term_wf_flag IN PA_RESOURCES.FUTURE_TERM_WF_FLAG%TYPE,
5078 		       x_return_status OUT	NOCOPY VARCHAR2,
5079 		       x_msg_data OUT NOCOPY VARCHAR2,
5080                        x_msg_count OUT NOCOPY NUMBER)
5081 IS
5082      l_resource_id  PA_RESOURCES.RESOURCE_ID%TYPE ;
5083 
5084      l_msg_index_out NUMBER;
5085 
5086 BEGIN
5087      -- initialize the error stack
5088      PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.set_fte_flag');
5089      -- initialize the return  status to success
5090      x_return_status := FND_API.G_RET_STS_SUCCESS;
5091 
5092      l_resource_id := pa_resource_utils.get_resource_id(p_person_id);
5093 
5094      IF NVL(l_resource_id,-999) <> -999 THEN
5095 
5096        UPDATE pa_resources
5097        SET future_term_wf_flag = p_future_term_wf_flag,
5098          last_update_date      = sysdate,
5099          last_updated_by       = fnd_global.user_id,
5100          last_update_login     = fnd_global.login_id
5101        WHERE
5102          resource_id = l_resource_id;
5103 
5104      ELSIF NVL(l_resource_id,-999) = -999 THEN
5105        x_return_status := FND_API.G_RET_STS_ERROR;
5106 
5107      END IF ; --IF l_resource_id <> -999
5108 
5109     -- reset the error stack
5110     PA_DEBUG.reset_err_stack;
5111 
5112 EXCEPTION
5113      WHEN OTHERS THEN
5114      x_return_status := FND_API.G_RET_STS_ERROR;
5115      x_msg_count := 1;
5116      x_msg_data  := substr(SQLERRM,1,240);
5117      FND_MSG_PUB.add_exc_msg( p_pkg_name => 'PA_RESOURCE_UTILS',
5118        p_procedure_name   => 'set_fte_flag');
5119        If x_msg_count = 1 THEN
5120           pa_interface_utils_pub.get_messages
5121             (p_encoded        => FND_API.G_TRUE,
5122              p_msg_index      => 1,
5123              p_msg_count      => x_msg_count,
5124              p_msg_data       => x_msg_data,
5125              p_data           => x_msg_data,
5126              p_msg_index_out  => l_msg_index_out );
5127        End If;
5128      raise;
5129 
5130 END set_fte_flag;
5131 
5132 --
5133 --  FUNCTION
5134 --              get_fte_flag
5135 --  PURPOSE
5136 --              This function gets the new future_term_wf_flag
5137 --              in table pa_resources for the passed person_id
5138 --  HISTORY
5139 --  05-MAR-207       kjai       Created for Bug 5683340
5140 --
5141 PROCEDURE Get_fte_flag(p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE,
5142                        x_future_term_wf_flag OUT NOCOPY PA_RESOURCES.FUTURE_TERM_WF_FLAG%TYPE,
5143                        x_return_status OUT  NOCOPY VARCHAR2,
5144                        x_msg_data      OUT  NOCOPY VARCHAR2,
5145                        x_msg_count OUT NOCOPY NUMBER)
5146 IS
5147      l_resource_id  PA_RESOURCES.RESOURCE_ID%TYPE ;
5148      l_future_term_wf_flag PA_RESOURCES.FUTURE_TERM_WF_FLAG%TYPE ;
5149 
5150      l_msg_index_out NUMBER;
5151 
5152 BEGIN
5153      -- initialize the error stack
5154      PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_fte_flag');
5155      -- initialize the return  status to success
5156      x_return_status := FND_API.G_RET_STS_SUCCESS;
5157 
5158      l_resource_id := pa_resource_utils.get_resource_id(p_person_id);
5159 
5160      IF NVL(l_resource_id,-999) <> -999 THEN
5161 
5162        SELECT pa_resources.future_term_wf_flag
5163        INTO l_future_term_wf_flag
5164        FROM pa_resources
5165        WHERE resource_id = l_resource_id;
5166 
5167      ELSIF NVL(l_resource_id,-999) = -999 THEN
5168 
5169        x_return_status := FND_API.G_RET_STS_ERROR;
5170        l_future_term_wf_flag := NULL ;
5171 
5172      END IF ;
5173 
5174      x_future_term_wf_flag := l_future_term_wf_flag ;
5175 
5176     -- reset the error stack
5177     PA_DEBUG.reset_err_stack;
5178 
5179 EXCEPTION
5180      WHEN OTHERS THEN
5181      x_future_term_wf_flag := NULL;
5182      x_return_status := FND_API.G_RET_STS_ERROR;
5183      x_msg_count := 1;
5184      x_msg_data  := substr(SQLERRM,1,240);
5185      FND_MSG_PUB.add_exc_msg( p_pkg_name => 'PA_RESOURCE_UTILS',
5186        p_procedure_name   => 'get_fte_flag');
5187        If x_msg_count = 1 THEN
5188           pa_interface_utils_pub.get_messages
5189             (p_encoded        => FND_API.G_TRUE,
5190              p_msg_index      => 1,
5191              p_msg_count      => x_msg_count,
5192              p_msg_data       => x_msg_data,
5193              p_data           => x_msg_data,
5194              p_msg_index_out  => l_msg_index_out );
5195        End If;
5196      raise;
5197 
5198 END get_fte_flag;
5199 
5200 --
5201 --  PROCEDURE
5202 --              is_fte
5203 --  PURPOSE
5204 --              This procedure checks whether the person is an FTE, as of sysdate.
5205 --              If he is, then returns the actual term date , wait days.
5206 --  HISTORY
5207 --  05-MAR-207       kjai       Created for Bug 5683340
5208 --
5209 PROCEDURE is_fte(p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE ,
5210                   x_return_end_date OUT	NOCOPY DATE ,
5211 		  x_wait_days OUT	NOCOPY NUMBER ,
5212 		  x_invol_term OUT	NOCOPY VARCHAR2,
5213 		  x_return_status OUT	NOCOPY VARCHAR2,
5214 		  x_msg_data OUT	NOCOPY VARCHAR2,
5215 		  x_msg_count OUT	NOCOPY NUMBER)
5216 IS
5217      l_resource_person_type PA_RESOURCES_DENORM.RESOURCE_PERSON_TYPE%TYPE ;
5218      l_end_date DATE ;
5219      l_valid_end_date DATE ;
5220      l_time_left NUMBER ;
5221 
5222      l_msg_index_out NUMBER;
5223 
5224 BEGIN
5225     -- initialize the error stack
5226      PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.is_fte');
5227      -- initialize the return  status to success
5228      x_return_status := FND_API.G_RET_STS_SUCCESS;
5229 
5230     SELECT  distinct(resource_person_type)
5231     INTO    l_resource_person_type
5232     FROM    pa_resources_denorm
5233     WHERE   person_id = p_person_id;
5234 
5235     IF ( l_resource_person_type = 'EMP') THEN
5236 
5237          SELECT TRUNC (NVL( MAX(actual_termination_date), SYSDATE ))
5238 	 INTO l_end_date
5239 	 FROM per_periods_of_service
5240          WHERE person_id = p_person_id
5241 	 AND actual_termination_date IS NOT NULL;
5242 
5243     ELSIF (l_resource_person_type = 'CWK' ) THEN
5244 
5245 	 SELECT TRUNC (NVL( MAX(actual_termination_date), SYSDATE ))
5246 	 INTO l_end_date
5247 	 FROM per_periods_of_placement
5248          WHERE person_id = p_person_id
5249          AND actual_termination_date IS NOT NULL;
5250 
5251     END IF ;  --IF (l_system_person_type = 'EMP' )
5252 
5253     IF (l_end_date > trunc(sysdate)) THEN
5254 
5255              pa_resource_utils.get_valid_enddate(p_person_id => p_person_id,
5256                                                  p_actual_term_date => l_end_date,
5257                                                  x_valid_end_date => l_valid_end_date,
5258 						 x_msg_data => x_msg_data,
5259                                                  x_msg_count => x_msg_count,
5260                                                  x_return_status => x_return_status);
5261 
5262 	     l_time_left := l_end_date - trunc(SYSDATE) +1 ; -- bug#8916777
5263 
5264              x_return_end_date := l_valid_end_date ;
5265 	     x_wait_days :=  l_time_left ;
5266 	     x_invol_term := 'Y' ;
5267 
5268     ELSE
5269              x_return_end_date := NULL ;
5270 	     x_wait_days :=  0 ;
5271 	     x_invol_term := 'N' ;
5272 
5273     END IF ; --(trunc(l_end_date) > trunc(sysdate))
5274 
5275     -- reset the error stack
5276     PA_DEBUG.reset_err_stack;
5277 
5278 EXCEPTION
5279      WHEN OTHERS THEN
5280      x_return_status := FND_API.G_RET_STS_ERROR;
5281      x_msg_count := 1;
5282      x_msg_data  := substr(SQLERRM,1,240);
5283      FND_MSG_PUB.add_exc_msg( p_pkg_name => 'PA_RESOURCE_UTILS',
5284        p_procedure_name   => 'is_fte');
5285        If x_msg_count = 1 THEN
5286           pa_interface_utils_pub.get_messages
5287             (p_encoded        => FND_API.G_TRUE,
5288              p_msg_index      => 1,
5289              p_msg_count      => x_msg_count,
5290              p_msg_data       => x_msg_data,
5291              p_data           => x_msg_data,
5292              p_msg_index_out  => l_msg_index_out );
5293        End If;
5294      raise;
5295 
5296 END is_fte;
5297 
5298 --
5299 --  PROCEDURE
5300 --              get_valid_enddate
5301 --  PURPOSE
5302 --              This procedure returns a valid end date if person is an FTE(as of sysdate)
5303 --
5304 --  HISTORY
5305 --  05-MAR-207       kjai       Created for Bug 5683340
5306 --
5307 PROCEDURE get_valid_enddate(p_person_id     IN PA_EMPLOYEES.PERSON_ID%TYPE ,
5308                             p_actual_term_date IN DATE  ,
5309 		            x_valid_end_date OUT NOCOPY DATE,
5310 			    x_return_status OUT	NOCOPY VARCHAR2,
5311                             x_msg_data OUT	NOCOPY VARCHAR2,
5312                             x_msg_count OUT	NOCOPY NUMBER)
5313 IS
5314        l_max_res_denorm_end_date DATE ;
5315 
5316        l_msg_index_out NUMBER;
5317 
5318 BEGIN
5319      -- initialize the error stack
5320      PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.get_valid_enddate');
5321      -- initialize the return  status to success
5322      x_return_status := FND_API.G_RET_STS_SUCCESS;
5323 
5324 
5325        SELECT TRUNC (MAX (resource_effective_end_date))
5326        INTO l_max_res_denorm_end_date
5327        FROM pa_resources_denorm
5328        WHERE person_id = p_person_id;
5329 
5330        IF ( (l_max_res_denorm_end_date <> to_date('31/12/4712','DD/MM/YYYY'))
5331             AND
5332             (l_max_res_denorm_end_date <> p_actual_term_date )
5333 	  ) THEN
5334 
5335             x_valid_end_date := l_max_res_denorm_end_date ;
5336 
5337       ELSE
5338 
5339            x_valid_end_date := to_date('31/12/4712','DD/MM/YYYY') ;
5340 
5341       END IF ;
5342 
5343     -- reset the error stack
5344     PA_DEBUG.reset_err_stack;
5345 
5346 EXCEPTION
5347   WHEN OTHERS THEN
5348      x_return_status := FND_API.G_RET_STS_ERROR;
5349      x_msg_count := 1;
5350      x_msg_data  := substr(SQLERRM,1,240);
5351      FND_MSG_PUB.add_exc_msg( p_pkg_name => 'PA_RESOURCE_UTILS',
5352        p_procedure_name   => 'get_valid_enddate');
5353        If x_msg_count = 1 THEN
5354           pa_interface_utils_pub.get_messages
5355             (p_encoded        => FND_API.G_TRUE,
5356              p_msg_index      => 1,
5357              p_msg_count      => x_msg_count,
5358              p_msg_data       => x_msg_data,
5359              p_data           => x_msg_data,
5360              p_msg_index_out  => l_msg_index_out );
5361        End If;
5362      raise;
5363 END get_valid_enddate;
5364 
5365 --
5366 --  PROCEDURE
5367 --              is_term_as_of_sys_date
5368 --  PURPOSE
5369 --              This procedure checks whether the employee / cwk
5370 --              is terminated as of sysdate
5371 --  HISTORY
5372 --   05-MAR-207       kjai       Created for Bug 5683340
5373 --
5374 PROCEDURE is_term_as_of_sys_date( itemtype                       IN      VARCHAR2
5375                                  , itemkey                       IN      VARCHAR2
5376                                  , actid                         IN      NUMBER
5377                                  , funcmode                      IN      VARCHAR2
5378                                  , resultout                     OUT     NOCOPY VARCHAR2) --File.Sql.39 bug 4440895
5379 IS
5380 
5381 CURSOR c_act_term_date (c_person_id PA_EMPLOYEES.PERSON_ID%TYPE)
5382 IS
5383 SELECT TRUNC (NVL (ACT_TERM_DATE, sysdate))
5384 FROM
5385 (SELECT MAX(actual_termination_date)"ACT_TERM_DATE"
5386  FROM per_periods_of_service
5387  WHERE person_id = c_person_id
5388  AND actual_termination_date IS NOT NULL
5389  UNION
5390  SELECT MAX(actual_termination_date)"ACT_TERM_DATE"
5391  FROM per_periods_of_placement
5392  WHERE person_id = c_person_id
5393  AND actual_termination_date IS NOT NULL )
5394 WHERE ACT_TERM_DATE IS NOT NULL ;
5395 
5396 
5397 l_person_id             PA_EMPLOYEES.PERSON_ID%TYPE;
5398 l_future_term_wf_flag pa_resources.future_term_wf_flag%TYPE ;
5399 l_end_date DATE ;
5400 
5401 l_msg_count                NUMBER;
5402 l_msg_data                VARCHAR(2000);
5403 l_return_status                VARCHAR2(1);
5404 
5405 l_pa_debug_mode VARCHAR2(1):= NVL(FND_PROFILE.value('PA_DEBUG_MODE'), 'N');
5406 
5407 BEGIN
5408 -- initialize the error stack
5409 --
5410    PA_DEBUG.init_err_stack('PA_RESOURCE_UTILS.is_term_as_of_sys_date');
5411 
5412 IF (l_pa_debug_mode = 'Y') THEN
5413  pa_debug.write('PA_RESOURCE_UTILS',
5414                 'log: ' || 'in procedure is_term_as_of_sys_date', 3);
5415 END IF;
5416 
5417 
5418 -- Get the workflow attribute values
5419 --
5420 l_person_id  := wf_engine.GetItemAttrNumber(itemtype        => itemtype,
5421                                             itemkey         => itemkey,
5422                                             aname           => 'PERSON_ID' );
5423 
5424 --get the future_term_wf_flag from pa_resources
5425 --
5426 pa_resource_utils.get_fte_flag(p_person_id => l_person_id,
5427 		               x_future_term_wf_flag => l_future_term_wf_flag,
5428                                x_msg_data => l_msg_data,
5429                                x_msg_count => l_msg_count,
5430                                x_return_status => l_return_status);
5431 
5432 IF (l_pa_debug_mode = 'Y') THEN
5433        pa_debug.write('PA_RESOURCE_UTILS',
5434                 'log: ' || 'in procedure is_term_as_of_sys_date, l_future_term_wf_flag: '||l_future_term_wf_flag, 3);
5435 END IF ;
5436 
5437 OPEN c_act_term_date(l_person_id);
5438 FETCH c_act_term_date INTO l_end_date;
5439 
5440 IF c_act_term_date%NOTFOUND THEN
5441    CLOSE c_act_term_date;
5442    resultout := wf_engine.eng_completed||':'||'E';
5443    IF (l_pa_debug_mode = 'Y') THEN
5444        pa_debug.write('PA_RESOURCE_UTILS',
5445                 'log: ' || 'in procedure is_term_as_of_sys_date, no end date found', 3);
5446    END IF;
5447 
5448 ELSE --IF c_act_term_date%NOTFOUND
5449 
5450    CLOSE c_act_term_date;
5451    IF (l_pa_debug_mode = 'Y') THEN
5452        pa_debug.write('PA_RESOURCE_UTILS',
5453                 'log: ' || 'in procedure is_term_as_of_sys_date, l_end_date: '||l_end_date, 3);
5454    END IF;
5455 
5456 
5457    IF ((l_future_term_wf_flag = 'Y') AND (l_end_date <= trunc(sysdate))) THEN   --Bug#9463127
5458        resultout := wf_engine.eng_completed||':'||'S';
5459    ELSE
5460        resultout := wf_engine.eng_completed||':'||'E';
5461    END IF ;
5462 
5463 END IF ; --IF c_act_term_date%NOTFOUND
5464 
5465 IF (l_pa_debug_mode = 'Y') THEN
5466  pa_debug.write('PA_RESOURCE_UTILS',
5467                 'log: ' || 'in procedure is_term_as_of_sys_date, resultout: '||resultout, 3);
5468 END IF;
5469 
5470 
5471 EXCEPTION
5472 WHEN OTHERS THEN
5473   wf_core.context('pa_resource_utils',
5474                             'is_term_as_of_sys_date',
5475                              itemtype,
5476                              itemkey,
5477                              to_char(actid),
5478                              funcmode);
5479   resultout := wf_engine.eng_completed||':'||'U';
5480 
5481 
5482 
5483 END is_term_as_of_sys_date;
5484 
5485 END pa_resource_utils ;