DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_RESOURCE_UTILS

Source


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