DBA Data[Home] [Help]

PACKAGE BODY: APPS.HR_NL_ORG_INFO

Source


1 PACKAGE BODY HR_NL_ORG_INFO AS
2 /* $Header: penlorgi.pkb 120.5.12020000.4 2013/02/04 10:11:59 mkuppuch ship $ */
3     g_package                  varchar2(33) := '  HR_NL_ORG_INFO.';
4     --
5     --
6     --Cursor which fetches Organizations from the named hierarchy-bottom to top
7     --
8     CURSOR org_hierarchy(p_org_id NUMBER) IS
9             SELECT p_org_id organization_id_parent
10                    ,0 lev
11             FROM dual
12             UNION
13             SELECT organization_id_parent
14                    ,level
15             FROM
16             (SELECT organization_id_parent
17                     ,organization_id_child
18               FROM per_org_structure_elements
19            WHERE org_structure_version_id = latest_named_hierarchy_vers(p_org_id)
20             )
21             START WITH organization_id_child    = p_org_id
22             CONNECT BY PRIOR organization_id_parent   = organization_id_child
23     ORDER BY lev;
24     --
25     --
26     -- Service function to return the current named hioerarchy.
27     --
28     FUNCTION named_hierarchy
29              (p_organization_id NUMBER) RETURN NUMBER IS
30       --
31       --
32       -- Cursor to return the current named hierarchy.
33       --
34       CURSOR c_hierarchy(vp_organization_id NUMBER) IS
35         SELECT TO_NUMBER(inf.org_information1) organization_structure_id
36         FROM   hr_organization_information inf
37               ,hr_all_organization_units   org
38         WHERE  org.organization_id         = vp_organization_id
39           AND  inf.organization_id         = org.business_group_id
40           AND  inf.org_information_context = 'NL_BG_INFO'
41           AND  inf.org_information1        IS NOT NULL;
42       --
43       --
44       -- Local Variables.
45       --
46       l_rec c_hierarchy%ROWTYPE;
47       l_proc varchar2(72) := g_package || '.named_hierarchy';
48     BEGIN
49       --
50       --
51       -- Find the current named organization hierarchy.
52       --
53       hr_utility.set_location('Entering ' || l_proc, 100);
54       OPEN  c_hierarchy(vp_organization_id => p_organization_id);
55       FETCH c_hierarchy INTO l_rec;
56       CLOSE c_hierarchy;
57       hr_utility.set_location('Leaving  ' || l_proc, 900);
58       --
59       --
60       -- Return ID.
61       --
62       RETURN l_rec.organization_structure_id;
63     EXCEPTION
64       when others then
65         hr_utility.set_location('Exception :' ||l_proc||SQLERRM(SQLCODE),999);
66     END named_hierarchy;
67     --
68     --
69     -- Service function to return the current version of the named hierarchy.
70     --
71     FUNCTION latest_named_hierarchy_vers
72             (p_organization_id NUMBER) RETURN NUMBER IS
73       --
74       --
75       -- Cursor to return the current named hierarchy version.
76       --
77       CURSOR c_hierarchy_version(vp_organization_id NUMBER) IS
78         SELECT sv.org_structure_version_id, sv.version_number
79         FROM   per_org_structure_versions  sv
80               ,fnd_sessions                ses
81         WHERE  sv.organization_structure_id = named_hierarchy(vp_organization_id)
82           AND  ses.session_id               = USERENV('sessionid')
83           AND  ses.effective_date BETWEEN sv.date_from
84           AND NVL(sv.date_to, Hr_general.End_Of_time)
85         ORDER BY sv.version_number DESC;
86       --
87       --
88       -- Local Variables.
89       --
90       l_rec c_hierarchy_version%ROWTYPE;
91       l_proc varchar2(72) := g_package || '.latest_named_hierarchy_vers';
92     BEGIN
93       hr_utility.set_location('Entering ' || l_proc, 100);
94       --
95       --
96       -- Find the current primary organization hierarchy.
97       --
98       OPEN  c_hierarchy_version(vp_organization_id => p_organization_id);
99       FETCH c_hierarchy_version INTO l_rec;
100       CLOSE c_hierarchy_version;
101       hr_utility.set_location('Leaving  ' || l_proc, 900);
102       --
103       --
104       -- Return ID.
105       --
106       RETURN l_rec.org_structure_version_id;
107     EXCEPTION
108       when others then
109         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
110 
111     END latest_named_hierarchy_vers;
112     --
113     --
114     -- Service function to see if organization belongs to the
115     -- current named hierarchy.
116     --
117     FUNCTION org_exists_in_hierarchy
118     (p_organization_id NUMBER) RETURN VARCHAR2 IS
119       --
120       --
121       -- Cursor to see if the organization belongs to the current
122       -- named hierarchy.
123       --
124       CURSOR c_org_exists(vp_organization_id NUMBER) IS
125         SELECT se.organization_id_child
126         FROM   per_org_structure_elements se
127         WHERE  se.org_structure_version_id =
128                latest_named_hierarchy_vers(vp_organization_id)
129           AND  (se.organization_id_parent  = vp_organization_id OR
130                 se.organization_id_child   = vp_organization_id);
131       --
132       --
133       -- Local Variables.
134       --
135       l_rec c_org_exists%ROWTYPE;
136       l_proc varchar2(72) := g_package || '.org_exists_in_hierarchy';
137     BEGIN
138       hr_utility.set_location('Entering ' || l_proc, 100);
139       OPEN  c_org_exists(vp_organization_id => p_organization_id);
140       FETCH c_org_exists INTO l_rec;
141       IF c_org_exists%FOUND THEN
142         CLOSE c_org_exists;
143         hr_utility.set_location('Leaving ' || l_proc, 900);
144         RETURN 'Y';
145       ELSE
146         CLOSE c_org_exists;
147         hr_utility.set_location('Leaving ' || l_proc, 910);
148         RETURN 'N';
149       END IF;
150     EXCEPTION
151       when others then
152         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
153     END org_exists_in_hierarchy;
154 
155     /* -----------------------------------------------------------------------
156     The procedure will return the value of the data item (Region and
157     Organization Number) required. The org_id taken as input is the org_id for
158     which the value is required.The procedure will navigate from the org_id
159     supplied up the hierarchy until it finds a value for the data item.        |
160     The following data items are required ;                                    |
161     Data Item       Column            Table                        Context     |
162     1. Region       org_information1  hr_organization_information  NL_ORG_INFO |
163     2. Org. Number  org_information1  hr_organization_information  NL_ORG_INFO |
164     ---------------------------------------------------------------------------*/
165 
166     PROCEDURE get_org_data_items(
167             p_org_id in number,
168             p_region  out nocopy varchar2,
169             p_organization_number out nocopy varchar2) IS
170      l_proc              varchar2(72) := g_package || '.get_org_data_items';
171      l_all_items_found   boolean := FALSE;
172      l_level             number;
173      l_organization_id   hr_organization_units.organization_id%type;
174      l_region     varchar2(255);
175      temp_region     varchar2(255);
176      l_organization_number     varchar2(255);
177      temp_organization_number     varchar2(255);
178      l_org_id                   hr_organization_units.organization_id%type;
179      l_org_information_context
180      hr_organization_information.org_information_context%type;
181     /* Add a check to see if the data item has a value for the org_id supplied
182     - add as a union or separate query */
183       CURSOR org_data_items
184       (l_org_id in hr_organization_units.organization_id%type) IS
185       select
186               substr(org_information1, 1, 30),
187               substr(org_information2, 1, 30)
188       from
189       hr_organization_units d,
190       hr_organization_information e
191       where
192       d.organization_id = e.organization_id and
193       d.organization_id = l_org_id and
194       e.org_information_context in ('NL_ORG_INFORMATION');
195     BEGIN
196       hr_utility.set_location('Entering ' || l_proc, 100);
197       temp_region := null;
198       temp_organization_number := null;
199       open org_hierarchy(p_org_id);
200       LOOP
201         fetch org_hierarchy into l_organization_id,l_level;
202         exit when org_hierarchy%NOTFOUND or l_all_items_found =TRUE ;
203 
204         --Fetch Organization Information
205         open org_data_items (l_organization_id);
206         fetch org_data_items into l_region,l_organization_number;
207         if org_data_items%found then
208           if l_region is not Null and temp_region is null then
209             temp_region := l_region;
210           end if;
211           if l_organization_number is not Null
212              and temp_organization_number is Null then
213                   temp_organization_number := l_organization_number;
214           end if;
215           if temp_region is not null and
216                  temp_organization_number is not null then
217                  l_all_items_found :=TRUE;
218           else
219                  l_all_items_found :=FALSE ;
220           end if;
221         end if;
222         close org_data_items;
223 
224      END LOOP;
225      close org_hierarchy;
226      p_region := temp_region;
227      p_organization_number := temp_organization_number;
228      hr_utility.set_location('Leaving  ' || l_proc, 900);
229 
230 
231     EXCEPTION
232       when others then
233         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
234         p_region := null;
235         p_organization_number := null;
236     END get_org_data_items;
237     /*------------------------------------------------------------------------
238     The following procedure checks if the Organization passed in exists in the
239     Primary Hierarchy.
240     --------------------------------------------------------------------------*/
241     PROCEDURE chk_for_org_in_hierarchy
242               (p_org_id in hr_organization_units.organization_id%TYPE,
243                p_exists out nocopy varchar2) IS
244      l_organization_id hr_organization_units.organization_id%TYPE;
245      l_level           number;
246      l_proc            varchar2(72) := g_package || '.chk_for_org_in_hierarchy';
247     BEGIN
248       hr_utility.set_location('Entering ' || l_proc, 100);
249       p_exists := org_exists_in_hierarchy(p_org_id);
250       hr_utility.set_location('Leaving  ' || l_proc, 100);
251     END chk_for_org_in_hierarchy;
252     --
253     --
254     -- Function checks to see if organization belongs to the same region from
255     -- the Org Hierarchy
256     --
257     FUNCTION Check_Org_In_Region
258             (p_org_id in hr_organization_units.organization_id%TYPE,
259             p_region in varchar2)
260     RETURN hr_organization_units.organization_id%TYPE IS
261      l_organization_id      hr_organization_units.organization_id%TYPE;
265      (vp_Organization_ID in hr_organization_units.organization_id%TYPE,
262      l_level                number;
263 
264      CURSOR cur_Region
266      vp_region in varchar2) IS
267      SELECT Organization_id,
268      org_information1 Region
269      FROM Hr_Organization_information
270      WHERE Organization_ID = vp_Organization_ID
271      AND Org_Information_Context='NL_ORG_INFORMATION';
272      v_cur_Region cur_Region%ROWTYPE;
273      --
274      --
275      -- Cursor which fetches Organizations from the named hierarchy
276      --
277      CURSOR org_named_hierarchy(vp_Organization_ID NUMBER) IS
278      SELECT vp_Organization_ID Organization_id,
279             0 lev
280      FROM dual
281      UNION
282      SELECT organization_id_parent
283       ,level lev
284      FROM
285      (
286      SELECT organization_id_parent
287      ,organization_id_child
288      FROM per_org_structure_elements
289      WHERE org_structure_version_id =
290      hr_nl_org_info.latest_named_hierarchy_vers(vp_Organization_ID)
291      )
292      START WITH organization_id_child= vp_Organization_ID
293      CONNECT BY PRIOR organization_id_parent= organization_id_child
294      ORDER BY lev;
295      v_org_hierarchy org_named_hierarchy%ROWTYPE;
296      b_RegionInfoFound boolean := FALSE;
297      l_proc   varchar2(72) := g_package || '.Check_Org_In_Region';
298     BEGIN
299       hr_utility.set_location('Entering ' || l_proc, 100);
300       IF p_region is NOT NULL THEN
301          OPEN org_named_hierarchy(p_org_id);
302          LOOP
303             hr_utility.set_location('Inside ' || l_proc, 105);
304             FETCH org_named_hierarchy INTO v_org_hierarchy;
305             EXIT WHEN org_named_hierarchy%NOTFOUND or b_RegionInfoFound=TRUE;
306             OPEN cur_Region(v_org_hierarchy.organization_id,p_region);
307             FETCH cur_Region INTO v_cur_Region;
308             hr_utility.set_location('Inside ' || l_proc, 110);
309             IF cur_Region%FOUND THEN
310               hr_utility.set_location('Inside ' || l_proc, 115);
311               IF v_cur_Region.Region IS NOT NULL AND
312                 v_cur_Region.Region=p_region THEN
313                 hr_utility.set_location('Inside ' || l_proc, 120);
314                 l_organization_id := p_org_id;
315                 b_RegionInfoFound := TRUE;
316               ELSIF v_cur_Region.Region IS NOT NULL AND
317                 v_cur_Region.Region<>p_region THEN
318                 hr_utility.set_location('Inside ' || l_proc, 125);
319                 l_organization_id := null;
320                 b_RegionInfoFound := TRUE;
321               END IF;
322             END IF;
323             CLOSE cur_Region;
324          END LOOP;
325          hr_utility.set_location('Inside ' || l_proc, 130);
326          CLOSE org_named_hierarchy;
327       END IF;
328       hr_utility.set_location('Leaving  ' || l_proc, 900);
329       return l_organization_id;
330     EXCEPTION
331       when others then
332         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
333     END Check_Org_In_Region;
334     -- Service function which returns the SI Provider information for the given organization.
335     -- It performs tree walk if SI information is not defined for the given organization.
336 
337     FUNCTION Get_SI_Org_Id
338         (p_organization_id NUMBER,p_si_type VARCHAR2,p_assignment_id NUMBER) RETURN NUMBER IS
339         l_proc  varchar2(72) := g_package || '.Get_SI_Org_Id';
340 
341 
342         --
343         -- Cursor which fetches Social Insurance Provider overridden at the Assignment Level
344         -- ordering the records by the si class order (A record for a Individual SI type would be
345         -- ordered higher than a AMI record).
346         CURSOR asg_provider
347         (l_org_id in hr_organization_units.organization_id%type,l_si_type varchar2,l_assgn_id NUMBER) IS
348          select pae.aei_information8 provider,
349          decode(pae.aei_information3,'AMI',0,1) si_class_order
350          from per_assignment_extra_info pae
351          ,fnd_sessions s
352          where assignment_id = l_assgn_id
353          and (pae.aei_information3=decode (l_si_type,'WEWE','WW','WEWA','WW',
354                         'WAOB','WAO','WAOD','WAO','PRIVATE_HEALTH','ZFW',l_si_type) or
355          pae.AEI_INFORMATION3 = DECODE(l_si_type,'WEWA','AMI','WEWE','AMI','WAOD','AMI','WAOB','AMI',
356                         'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
357                         'ZVW','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type))
358         and s.effective_date between
359         fnd_date.canonical_to_date(pae.aei_information1)
360         and nvl(fnd_date.canonical_to_date(pae.aei_information2),s.effective_date) AND
361         s.session_id=userenv('sessionid')
362         order by si_class_order desc;
363 
364         --
365         -- Cursor which fetches Social Insurance Provider for the given Hr Organization
366         -- and which offers si class ordering the records first by the Primary provider Flag
367         -- and then by the si class order(A record for a Individual SI type would be
368         -- ordered higher than a AMI record).
369         CURSOR org_uwv_provider
370         (l_org_id in hr_organization_units.organization_id%type,
371          l_uwv_id in hr_organization_units.organization_id%type,
372          l_si_type varchar2) IS
373          select
374          e.org_information_id,
375          e.org_information4 provider,nvl(e.org_information7,'N') p_flag,
376          decode(e.org_information3,'AMI',0,1) si_class_order
377          from
378          hr_organization_information e
379          ,fnd_sessions s
380          where
381          e.organization_id=l_org_id and
382          e.org_information_context = 'NL_SIP' and
386                         'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
383          (e.org_information3=DECODE(l_si_type,'WEWE','WW','WEWA','WW','WAOB','WAO','WAOD','WAO',
384                              'PRIVATE_HEALTH','ZFW',l_si_type) or
385          e.org_information3 = DECODE(l_si_type,'WEWE','AMI','WEWA','AMI','WAOB','AMI','WAOD','AMI',
387                         'ZVW','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type)) and
388          e.org_information4 = NVL(l_uwv_id,e.org_information4)
389          and s.effective_date between
390            fnd_date.canonical_to_date(e.org_INFORMATION1)
391            and nvl(fnd_date.canonical_to_date(e.org_INFORMATION2),s.effective_date) AND
392          s.session_id=userenv('sessionid')
393          order by p_flag desc,si_class_order desc;
394 
395         v_asg_provider      asg_provider%ROWTYPE;
396         v_org_uwv_provider  org_uwv_provider%ROWTYPE;
397         l_level             number;
398         l_organization_id   hr_organization_units.organization_id%TYPE;
399         l_org_found            boolean := false;
400         l_uwv_org_id         hr_organization_units.organization_id%TYPE;
401         l_org_info_id             hr_organization_units.organization_id%TYPE;
402      BEGIN
403         /* Fetch Override Ins Provider at the Asg Level*/
404         OPEN asg_provider(p_organization_id,p_si_type,p_assignment_id);
405         FETCH asg_provider INTO v_asg_provider;
406         CLOSE asg_provider;
407 
408 
409         /* If Ins Provider at the Asg Level is specified*/
410         IF v_asg_provider.provider IS NOT NULL THEN
411            l_uwv_org_id := v_asg_provider.provider;
412            hr_utility.set_location('Asg Level UWV Prov l_uwv_org_id'||l_uwv_org_id,100);
413         END IF;
414 
415         /* If Ins Provider at the Asg Level is not specified
416         tree walk to find the Primary Insurance Provider at the level */
417         --hr_utility.set_location('Calling Get_SI_Org_Id',200);
418 
419         l_org_found := FALSE;
420         l_org_info_id := -1;
421         if org_hierarchy%ISOPEN then
422             CLOSE org_hierarchy;
423         END IF;
424         /*Start looking for the UWV Provider beginning from the HR Org
425         of Employee */
426 
427         OPEN org_hierarchy(p_organization_id);
428         LOOP
429             FETCH org_hierarchy into l_organization_id,l_level;
430             exit when org_hierarchy%NOTFOUND or l_org_found =TRUE ;
431             --hr_utility.set_location(' l_organization_id'||l_organization_id||' level '||l_level,300);
432             --Fetch UWV Provider assigned to the HR Organization
433             open org_uwv_provider(l_organization_id,l_uwv_org_id,p_si_type);
434             FETCH org_uwv_provider into v_org_uwv_provider;
435             if org_uwv_provider%found then
436                 --hr_utility.set_location(' l_organization_id'||l_organization_id||' p_organization_id '||p_organization_id,310);
437                 if l_organization_id =p_organization_id then
438                     /*Assign the UWV Provider defined at the HR Org
439                     But continue further to see if any Primary
440                     UWV exists up in the hierarchy*/
441                     l_org_info_id := v_org_uwv_provider.org_information_id;
442                     --hr_utility.set_location(' Assign -HR Org l_org_info_id'||l_org_info_id,320);
443                 else
444                     /*Assign the UWV Provider defined at the Parent HR Org if
445                     not overridden at the HR Org Level*/
446                     if l_org_info_id =-1 then
447                         l_org_info_id := v_org_uwv_provider.org_information_id;
448                         --hr_utility.set_location(' Parent HR Org l_org_info_id'||l_org_info_id,330);
449                     end if;
450                 end if;
451                 /*Check If the UWV Provider assigned is also the Primary
452                  Quit Searching the hierarchy*/
453                 if v_org_uwv_provider.p_flag='Y' then
454                     l_org_found:=TRUE;
455                     l_org_info_id :=  v_org_uwv_provider.org_information_id;
456                     --hr_utility.set_location(' Primary UWV l_org_info_id'||l_org_info_id,340);
457                 end if;
458             end if;
459             close org_uwv_provider;
460         END LOOP;
461         close org_hierarchy;
462         --hr_utility.set_location('Org Info Id :'||l_org_info_id||' UWV From Hierarchy l_uwv_org_id'||l_uwv_org_id,350);
463         RETURN l_org_info_id;
464      EXCEPTION
465         when others then
466         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
467         IF org_hierarchy%ISOPEN THEN
468           CLOSE org_hierarchy;
469         END IF;
470         RETURN -1;
471     END Get_SI_Org_Id;
472 
473 
474     -- Service function which returns the SI Provider information for the given organization.
475     -- It performs tree walk if SI information is not defined for the given organization.
476     --
477 
478     FUNCTION Get_SI_Provider_Info
479         (p_organization_id NUMBER,p_si_type VARCHAR2,p_assignment_id NUMBER) RETURN NUMBER IS
480 
481         l_proc            varchar2(72) := g_package || '.Get_SI_Provider_Info';
482         l_provider_info   hr_organization_units.organization_id%type;
483         l_org_id          hr_organization_units.organization_id%type;
484 
485 
486         --
487         -- Cursor which fetches Social Insurance Provider overridden at the Assignment Level
488         -- ordering the records by the si class order (A record for a Individual SI type would be
489         -- ordered higher than a AMI record).
490         CURSOR asg_provider
491         (l_org_id in hr_organization_units.organization_id%type,l_si_type varchar2,l_assgn_id NUMBER) IS
492          select pae.aei_information8 provider,
493          decode(pae.aei_information3,'AMI',0,1) si_class_order
494          from per_assignment_extra_info pae
495          ,fnd_sessions s
496          where assignment_id = l_assgn_id
497          and (pae.aei_information3=decode (l_si_type,'WEWE','WW','WEWA','WW',
498                         'WAOB','WAO','WAOD','WAO','PRIVATE_HEALTH','ZFW',l_si_type) or
499          pae.aei_information3 = DECODE(l_si_type,'WEWE','AMI','WEWA','AMI',
500                         'WAOB','AMI','WAOD','AMI',
501                         'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
502                         'ZVW','AMI','ZVWL','AMI','ZVWS','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type))
503         and s.effective_date between
504         fnd_date.canonical_to_date(pae.aei_information1)
505         and nvl(fnd_date.canonical_to_date(pae.aei_information2),s.effective_date) AND
506         s.session_id=userenv('sessionid')
507         order by si_class_order desc;
508 
509         --
510         -- Cursor which fetches Social Insurance Provider for the given Hr Organization
511         -- and which offers SI type ordering the records first by the Primary provider Flag
512         -- and then by the si class order(A record for a Individual SI type would be
513         -- ordered higher than a AMI record).
514         CURSOR org_uwv_provider
515         (l_org_id in hr_organization_units.organization_id%type,l_si_type varchar2) IS
516          select
517          e.org_information4 provider,nvl(e.org_information7,'N') p_flag,
518          decode(e.org_information3,'AMI',0,1) si_class_order
519          from
520          hr_organization_information e
521          ,fnd_sessions s
522          where
523          e.organization_id=l_org_id and
524          e.org_information_context = 'NL_SIP' and
525          (e.org_information3=DECODE(l_si_type,'WEWE','WW','WEWA','WW','WAOB','WAO','WAOD','WAO',
526                              'PRIVATE_HEALTH','ZFW',l_si_type) or
527          e.org_information3 = DECODE(l_si_type,'WEWE','AMI','WEWA','AMI','WAOB','AMI','WAOD','AMI',
528                         'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
529                         'ZVW','AMI','ZVWL','AMI','ZVWS','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type)) and
530          s.effective_date between
531            fnd_date.canonical_to_date(e.org_INFORMATION1)
532            and nvl(fnd_date.canonical_to_date(e.org_INFORMATION2),s.effective_date) AND
533          s.session_id=userenv('sessionid')
534          order by p_flag desc,si_class_order desc;
535 
536         v_asg_provider      asg_provider%ROWTYPE;
537         v_org_uwv_provider  org_uwv_provider%ROWTYPE;
538         l_level             number;
539         l_organization_id   hr_organization_units.organization_id%TYPE;
540         l_uwv_found            boolean := false;
541         l_uwv_org_id         hr_organization_units.organization_id%TYPE;
542      BEGIN
543         /* Fetch Override Ins Provider at the Asg Level*/
544         OPEN asg_provider(p_organization_id,p_si_type,p_assignment_id);
545         FETCH asg_provider INTO v_asg_provider;
546         CLOSE asg_provider;
547 
548 
549         /* If Ins Provider at the Asg Level is specified*/
550         IF v_asg_provider.provider IS NOT NULL THEN
551            l_uwv_org_id := v_asg_provider.provider;
552            --hr_utility.set_location('Asg Level UWV Prov l_uwv_org_id'||l_uwv_org_id,100);
553         ELSE
554             /* If Ins Provider at the Asg Level is not specified
555             tree walk to find the Primary Insurance Provider at the level */
556             --hr_utility.set_location('Calling Get_SI_Org_Id',200);
557 
558             l_uwv_found := FALSE;
559             l_uwv_org_id := -1;
560             if org_hierarchy%ISOPEN then
561                 CLOSE org_hierarchy;
562             END IF;
563             /*Start looking for the UWV Provider beginning from the HR Org
564             of Employee */
565 
566             OPEN org_hierarchy(p_organization_id);
567             LOOP
568                 FETCH org_hierarchy into l_organization_id,l_level;
569                 exit when org_hierarchy%NOTFOUND or l_uwv_found =TRUE ;
570                 --hr_utility.set_location(' l_organization_id'||l_organization_id||' level '||l_level,300);
571                 --Fetch UWV Provider assigned to the HR Organization
572                 open org_uwv_provider(l_organization_id,p_si_type);
576                     if l_organization_id =p_organization_id then
573                 FETCH org_uwv_provider into v_org_uwv_provider;
574                 if org_uwv_provider%found then
575                     --hr_utility.set_location(' l_organization_id'||l_organization_id||' p_organization_id '||p_organization_id,310);
577                         /*Assign the UWV Provider defined at the HR Org
578                         But continue further to see if any Primary
579                         UWV exists up in the hierarchy*/
580                         l_uwv_org_id := v_org_uwv_provider.provider;
581                         --hr_utility.set_location(' Assign -HR Org l_uwv_org_id'||l_uwv_org_id,320);
582                     else
583                         /*Assign the UWV Provider defined at the Parent HR Org
584                         if not overridden at the HR Org Level*/
585                         if l_uwv_org_id =-1 then
586                             l_uwv_org_id := v_org_uwv_provider.provider;
587                             --hr_utility.set_location(' Parent HR Org l_uwv_org_id'||l_uwv_org_id,330);
588                         end if;
589                     end if;
590                     /*Check If the UWV Provider assigned is also the Primary
591                      Quit Searching the hierarchy*/
592                     if v_org_uwv_provider.p_flag='Y' then
593                         l_uwv_found:=TRUE;
594                         l_uwv_org_id := v_org_uwv_provider.provider;
595                         --hr_utility.set_location(' Primary UWV l_uwv_org_id'||l_uwv_org_id||' @ '||l_organization_id,340);
596                     end if;
597 
598                 end if;
599                 close org_uwv_provider;
600             END LOOP;
601             close org_hierarchy;
602             --hr_utility.set_location(' UWV From Hierarchy l_uwv_org_id'||l_uwv_org_id,350);
603 
604         END IF;
605         --hr_utility.set_location(' UWV ID -> l_uwv_org_id'||l_uwv_org_id,360);
606         RETURN l_uwv_org_id;
607      EXCEPTION
608         when others then
609         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
610         IF org_hierarchy%ISOPEN THEN
611           CLOSE org_hierarchy;
612         END IF;
613         RETURN -1;
614      END Get_SI_Provider_Info;
615 
616      --
617      -- Service function which returns the SI Provider information for the given assignment.
618      -- Its an Over Loaded Function ,fetches the Org Id and then calls the
619      -- other Over Loaded Function to Tree Walk and Fetch the provider info.
620      FUNCTION Get_SI_Provider_Info
621         (p_assignment_id NUMBER,p_si_type VARCHAR2) RETURN NUMBER IS
622 
623         --Determine the Organization Id of the Employees Assignment
624         CURSOR get_org_id(p_assignment_id number) is
625         select paa.organization_id
626         from per_all_assignments_f paa,fnd_sessions ses
627         where paa.assignment_id = p_assignment_id and
628         ses.effective_date between paa.effective_start_date and paa.effective_end_date and
629         session_id = userenv('sessionid');
630 
631         l_org_id per_all_assignments_f.organization_id%TYPE;
632         l_provider_id hr_organization_units.organization_id%TYPE;
633 
634      BEGIN
635 
636         OPEN get_org_id(p_assignment_id);
637         FETCH get_org_id into l_org_id;
638         CLOSE get_org_id;
639 
640         l_provider_id:=Get_SI_Provider_Info(l_org_id,p_si_type,p_assignment_id);
641 
642         RETURN l_provider_id;
643 
644      END Get_SI_Provider_Info;
645 
646      --
647      --
648      -- Service function to see if uwv organization is assigned to
649      -- any hr organization in the hierarchy.
650      --
651      FUNCTION check_uwv_org_in_hierarchy
652        (p_uwv_org_id NUMBER,p_organization_id NUMBER) RETURN VARCHAR2 IS
653         --
654         --
655         -- Cursor to see if the organization belongs to the current
656         -- named hierarchy.
657         --
658         CURSOR org_uwv_provider
659         (l_uwv_org_id in hr_organization_units.organization_id%type,
660         l_org_id in hr_organization_units.organization_id%type) IS
661          select
662          e.org_information4 provider
663          from
664          hr_organization_information e
665          where
666          e.organization_id=l_org_id and
667          e.org_information_context = 'NL_SIP' and
668          e.org_information4 =l_uwv_org_id ;
669         --
670         --
671         -- Local Variables.
672         --
673         l_uwv_found varchar2(1) := 'N';
674         l_proc varchar2(72) := g_package || '.check_uwv_org_in_hierarchy';
675         l_level             number;
676         l_organization_id   hr_organization_units.organization_id%TYPE;
677         v_org_uwv_provider  org_uwv_provider%ROWTYPE;
678      BEGIN
679         l_uwv_found := 'N';
680         IF org_hierarchy%ISOPEN THEN
681             CLOSE org_hierarchy;
682         END IF;
683         /*Start looking for the UWV Provider beginning from the HR Org
684         of Employee */
685 
686         OPEN org_hierarchy(p_organization_id);
687         LOOP
691             --Fetch UWV Provider assigned to the HR Organization
688             FETCH org_hierarchy into l_organization_id,l_level;
689             exit when org_hierarchy%NOTFOUND or l_uwv_found ='Y' ;
690             --hr_utility.set_location(' l_organization_id'||l_organization_id||' level '||l_level,300);
692             open org_uwv_provider(p_uwv_org_id,l_organization_id);
693             FETCH org_uwv_provider into v_org_uwv_provider;
694             IF org_uwv_provider%FOUND THEN
695                 l_uwv_found := 'Y';
696             END IF;
697             CLOSE org_uwv_provider;
698         END LOOP;
699         CLOSE org_hierarchy;
700         RETURN l_uwv_found;
701      EXCEPTION
702        when others then
703         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
704         IF org_hierarchy%ISOPEN THEN
705             CLOSE org_hierarchy;
706         END IF;
707         RETURN l_uwv_found;
708      END check_uwv_org_in_hierarchy;
709     --
710     -- Service function to return the Info Id from the Assignment Extra Information
711     -- to support AMI Enhancement
712     -- Returns the ID for the Specified SI type defined,if not defined looks for a AMI
713     -- record and returns it.
714     FUNCTION Get_Asg_SII_Info_ID
715     (p_assignment_id NUMBER,p_si_type VARCHAR2) RETURN NUMBER IS
716         --
717         -- Cursor which fetches Social Insurance Provider overridden at the Assignment Level
718         -- ordering the records by the si class order (A record for a Individual SI type would be
719         -- ordered higher than a AMI record).
720         CURSOR asg_provider
721         (l_assgn_id NUMBER,l_si_type varchar2) IS
722         select pae.assignment_extra_info_id,
723         decode(pae.aei_information3,'AMI',0,1) si_class_order
724         from per_assignment_extra_info pae
725         ,fnd_sessions s
726         where assignment_id = l_assgn_id
727         and (pae.aei_information3=decode (l_si_type,'WEWE','WW','WEWA','WW',
728                     'WAOB','WAO','WAOD','WAO','PRIVATE_HEALTH','ZFW',l_si_type) or
729         pae.AEI_INFORMATION3 = DECODE(l_si_type,'WEWA','AMI','WEWE','AMI','WAOD','AMI','WAOB','AMI',
730                     'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
731                     'ZVW','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type))
732         and s.effective_date between
733         fnd_date.canonical_to_date(pae.aei_information1)
734         and nvl(fnd_date.canonical_to_date(pae.aei_information2),s.effective_date)
735         and session_id = userenv('sessionid')
736         order by si_class_order desc;
737         v_asg_provider      asg_provider%ROWTYPE;
738     BEGIN
739         OPEN asg_provider(p_assignment_id,p_si_type);
740         FETCH asg_provider INTO v_asg_provider;
741         CLOSE asg_provider;
742 
743         RETURN v_asg_provider.assignment_extra_info_id;
744     END Get_Asg_SII_Info_ID;
745 
746     -- Function which returns average days per month for the given organization
747     -- If the value is not specified for the given organization it performs the tree walk.
748 
749     FUNCTION Get_Avg_Days_Per_Month
750     (p_assignment_id NUMBER) RETURN NUMBER IS
751     --
752     --Determine the Organization Id of the Employees Assignment
753     --
754     CURSOR get_org_id(p_assignment_id number) is
755     select paa.organization_id
756     from per_all_assignments_f paa,fnd_sessions ses
757     where paa.assignment_id = p_assignment_id and
758     ses.effective_date between paa.effective_start_date and paa.effective_end_date and
759     session_id = userenv('sessionid');
760 
761     --
762     --Cursor which fetches Tax Information for the given HR Organization
763     --
764     CURSOR Avg_Days_Per_Month
765     (l_org_id in hr_organization_units.organization_id%type) IS
766      select
767      e.org_information_id,
768      e.org_information5 Avg_days_Per_Month
769      from
770      hr_organization_information e
771      where
772      e.organization_id=l_org_id and
773      e.org_information_context= 'NL_ORG_INFORMATION'
774      and e.org_information5 IS NOT NULL;
775     --
776     --Local Variables
777     --
778     l_avg_days        Number;
779     v_avg_days          Avg_Days_Per_Month%ROWTYPE;
780     l_org_id            per_all_assignments_f.organization_id%TYPE;
781     l_organization_id   hr_organization_units.organization_id%TYPE;
782     l_level             number;
783 
784  BEGIN
785     --
786     --Determine the Organization Id of the Employees Assignment
787     --
788     OPEN get_org_id(p_assignment_id);
789     FETCH get_org_id into l_org_id;
790     CLOSE get_org_id;
791 
792     l_avg_days := Null;
793     --
794     --Check whether the Average Days Per Month is specified for the Organization
795     --
796     OPEN Avg_Days_Per_Month(l_org_id);
797     Fetch Avg_Days_Per_Month into v_avg_days;
798     If Avg_Days_Per_Month%FOUND and v_avg_days.Avg_days_Per_Month is not null then
799     l_avg_days:= v_avg_days.Avg_days_Per_Month;
800     End if;
801     Close Avg_Days_Per_Month;
802 
803     --If the Average days per month is not specified tree walk to find the organization with
804     --the same value defined.
805     --
806     IF l_avg_days IS NULL THEN
807 
808     if org_hierarchy%ISOPEN then
809     CLOSE org_hierarchy;
810     END IF;
811 
812     OPEN org_hierarchy(l_org_id);
813     LOOP
814         FETCH org_hierarchy into l_organization_id,l_level;
815         exit when org_hierarchy%NOTFOUND or l_avg_days IS NOT NULL;
816         --
817         --Fetch the avg days per month for the given organization
818         --
819         open Avg_Days_Per_Month(l_organization_id);
820         FETCH Avg_Days_Per_Month into v_avg_days;
821         if Avg_Days_Per_Month%found and v_avg_days.Avg_days_Per_Month is not null then
822         l_avg_days:= v_avg_days.Avg_days_Per_Month;
823         end if;
824         close Avg_Days_Per_Month;
825     END LOOP;
826     close org_hierarchy;
827 
828     END IF;
829     --If the value for average days per month is not specified anywhere up in the hierarchy default it to 30
830     IF l_avg_days IS NULL THEN
831     l_avg_days:=30;
832     END IF;
833 
834     RETURN l_avg_days;
835  EXCEPTION
836     when others then
837     --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
838     IF org_hierarchy%ISOPEN THEN
839       CLOSE org_hierarchy;
840     END IF;
841     RETURN 0;
842  END Get_Avg_Days_Per_Month;
843      --
844      --Function which returns the tax organization for the given organization by traversing the org hierarchy
845      --
846 Function Get_Tax_Org_Id(p_org_structure_version_id NUMBER,p_organization_id NUMBER) RETURN NUMBER IS
847     --
848     -- Cursor which fetches Tax Information for the given HR Organization
849     --
850     CURSOR tax_organization
851     (l_org_id in hr_organization_units.organization_id%type) IS
852      select
853      e.org_information_id,
854      e.org_information4 tax_information
855      from
856      hr_organization_information e
857      where
858      e.organization_id=l_org_id and
859      e.org_information_context= 'NL_ORG_INFORMATION'
860      and e.org_information3 IS NOT NULL
861      and e.org_information4 IS NOT NULL;
862 
863 
864     --
865     -- Cursor which fetches Tax Organization list for the given HR Organization
866     --
867     CURSOR tax_org_hierarchy(l_org_struct_version_id in per_org_structure_versions.org_structure_version_id%type,
868     l_org_id in hr_organization_units.organization_id%type) IS
869     SELECT tax_org_id,lev from hr_organization_information e,(
870         SELECT l_org_id tax_org_id,0 lev from dual
871         UNION
872         SELECT distinct organization_id_parent
873                    ,level
874             FROM (
875                 SELECT distinct organization_id_parent, organization_id_child
876                 FROM per_org_structure_elements pose
877                  where   pose.org_structure_version_id = l_org_struct_version_id)
878         START WITH organization_id_child    = l_org_id
879         CONNECT BY PRIOR organization_id_parent   = organization_id_child)
880     where
881     e.organization_id=tax_org_id and
882     e.org_information_context= 'NL_ORG_INFORMATION'
883     and e.org_information3 IS NOT NULL
884     and e.org_information4 IS NOT NULL
885     ORDER BY lev;
886 
887     v_tax_org           tax_organization%ROWTYPE;
888     l_level             number;
889     l_tax_org_id         hr_organization_units.organization_id%TYPE;
890 
891 BEGIN
892 l_tax_org_id := NULL;
893 
894     OPEN tax_organization(p_organization_id);
895     Fetch tax_organization into v_tax_org;
896     If tax_organization%FOUND and v_tax_org.tax_information is not null then
897     l_tax_org_id:= p_organization_id;
898     End if;
899     Close tax_organization;
900 
901     if tax_org_hierarchy%ISOPEN then
902     CLOSE tax_org_hierarchy;
903     end if;
904 
905     /*Fetch the tax organization list with tax information defined beginning from the HR Org */
906     if l_tax_org_id IS NULL then
907     OPEN tax_org_hierarchy(p_org_structure_version_id,p_organization_id);
908     FETCH tax_org_hierarchy into l_tax_org_id,l_level;
909     close tax_org_hierarchy;
910     end if;
911 
912     RETURN l_tax_org_id;
913 
914 EXCEPTION
915 when others then
916     --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
917     IF tax_org_hierarchy%ISOPEN THEN
918       CLOSE tax_org_hierarchy;
919     END IF;
920 RETURN null;
921 END Get_Tax_Org_Id;
922 
923 
924         FUNCTION Get_Working_hours_Per_Week
925         (p_org_id NUMBER) RETURN NUMBER IS
926         --
927         --Determine the Organization Id of the Employees Assignment
928         --
929         CURSOR get_org_id(p_assignment_id number) is
930         select paa.organization_id
931         from per_all_assignments_f paa,fnd_sessions ses
932         where paa.assignment_id = p_assignment_id and
933         ses.effective_date between paa.effective_start_date and paa.effective_end_date and
934         session_id = userenv('sessionid');
935 
936         --
937         --
938 
939         CURSOR Working_hours_Per_Week
940         (l_org_id in hr_organization_units.organization_id%type) IS
941          select
942          e.org_information_id,
943          e.org_information7 working_hours
944          from
945          hr_organization_information e
946          where
947          e.organization_id=l_org_id and
948          e.org_information_context= 'NL_ORG_INFORMATION'
949          and e.org_information7 IS NOT NULL;
950         --
951         --Local Variables
952         --
953         l_working_hrs          Number;
954         v_hrs_per_week      Working_hours_Per_Week%ROWTYPE;
955         l_org_id            per_all_assignments_f.organization_id%TYPE;
956         l_organization_id   hr_organization_units.organization_id%TYPE;
957         l_level             number;
958 
959  BEGIN
960         --
961         --
962 
963         l_working_hrs:= Null;
964         --
965         --Check whether the Working_hours_Per_Week is specified for the Organization
966         --
967         OPEN Working_hours_Per_Week(p_org_id);
968         Fetch Working_hours_Per_Week into v_hrs_per_week;
969         If Working_hours_Per_Week%FOUND and v_hrs_per_week.working_hours is not null then
970         l_working_hrs:= v_hrs_per_week.working_hours;
971         End if;
972         Close Working_hours_Per_Week;
973 
974        hr_utility.trace('l_working_hours is : '||l_working_hrs);
975 
976         --If the Working_hours_Per_Week is not specified tree walk to find the organization with
977         --the same value defined.
978         --
979         IF l_working_hrs IS NULL THEN
980 
981         if org_hierarchy%ISOPEN then
982         CLOSE org_hierarchy;
983         END IF;
984 
985         OPEN org_hierarchy(p_org_id);
986         LOOP
987                 FETCH org_hierarchy into l_organization_id,l_level;
988                 exit when org_hierarchy%NOTFOUND or l_working_hrs IS NOT NULL;
989                 --
990                 --
991                 OPEN Working_hours_Per_Week(l_organization_id);
992                 Fetch Working_hours_Per_Week into v_hrs_per_week;
993         If Working_hours_Per_Week%FOUND and v_hrs_per_week.working_hours is not null then
994                 l_working_hrs:= v_hrs_per_week.working_hours;
995                 hr_utility.trace('l_working_hours from hierarchy is : '||l_working_hrs);
996                 end if;
997                 Close Working_hours_Per_Week;
998         END LOOP;
999         close org_hierarchy;
1000 
1001         END IF;
1002 
1003 
1004         RETURN l_working_hrs;
1005  EXCEPTION
1006         when others then
1007         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1008         IF org_hierarchy%ISOPEN THEN
1009           CLOSE org_hierarchy;
1010         END IF;
1011         RETURN 0;
1012  END Get_Working_hours_Per_Week;
1013 
1017     FUNCTION Get_Part_Time_Perc_Method
1014 -- Function which returns part time percentage method for the given organization
1015 -- If the value is not specified for the given organization it performs the tree walk.
1016 
1018     (p_assignment_id NUMBER) RETURN NUMBER IS
1019     --
1020     --Determine the Organization Id of the Employees Assignment
1021     --
1022     CURSOR get_org_id(p_assignment_id number) is
1023     select paa.organization_id
1024     from per_all_assignments_f paa,fnd_sessions ses
1025     where paa.assignment_id = p_assignment_id and
1026     ses.effective_date between paa.effective_start_date and paa.effective_end_date and
1027     session_id = userenv('sessionid');
1028 
1029     --
1030     --Cursor which fetches Part Time Percetage Method for the given HR Organization
1031     --
1032     CURSOR Part_Time_Percentage_Method
1033     (l_org_id in hr_organization_units.organization_id%type) IS
1034      select
1035      e.org_information_id,
1036      e.org_information8 Part_Time_Percentage_Method
1037      from
1038      hr_organization_information e
1039      where
1040      e.organization_id=l_org_id and
1041      e.org_information_context= 'NL_ORG_INFORMATION'
1042      and e.org_information8 IS NOT NULL;
1043     --
1044     --Local Variables
1045     --
1046     l_part_time_per        Number;
1047     v_part_time_per     Part_Time_Percentage_Method%ROWTYPE;
1048     l_org_id            per_all_assignments_f.organization_id%TYPE;
1049     l_organization_id   hr_organization_units.organization_id%TYPE;
1050     l_level             number;
1051 
1052  BEGIN
1053     --
1054     --Determine the Organization Id of the Employees Assignment
1055     --
1056     OPEN get_org_id(p_assignment_id);
1057     FETCH get_org_id into l_org_id;
1058     CLOSE get_org_id;
1059 
1060     l_part_time_per := Null;
1061     --
1062     --Check whether the Part Time Percetage Method is specified for the Organization
1063     --
1064     OPEN Part_Time_Percentage_Method(l_org_id);
1065     Fetch Part_Time_Percentage_Method into v_part_time_per;
1066     If Part_Time_Percentage_Method%FOUND and v_part_time_per.Part_Time_Percentage_Method is not null then
1067     l_part_time_per:= v_part_time_per.Part_Time_Percentage_Method;
1068     End if;
1069     Close Part_Time_Percentage_Method;
1070 
1071      --If the Part Time Percetage Method is not specified tree walk to find the organization
1072     --with the same value defined.
1073     --
1074     IF l_part_time_per IS NULL THEN
1075 
1076     if org_hierarchy%ISOPEN then
1077     CLOSE org_hierarchy;
1078     END IF;
1079 
1080     OPEN org_hierarchy(l_org_id);
1081     LOOP
1082         FETCH org_hierarchy into l_organization_id,l_level;
1083         exit when org_hierarchy%NOTFOUND or l_part_time_per IS NOT NULL;
1084         --
1085         --Fetch the Part Time Percetage Method for the given organization
1086         --
1087         open Part_Time_Percentage_Method(l_organization_id);
1088         FETCH Part_Time_Percentage_Method into v_part_time_per;
1089         if Part_Time_Percentage_Method%found and v_part_time_per.Part_Time_Percentage_Method is not null then
1090         l_part_time_per:= v_part_time_per.Part_Time_Percentage_Method;
1091         end if;
1092         close Part_Time_Percentage_Method;
1093     END LOOP;
1094     close org_hierarchy;
1095 
1096     END IF;
1097     IF l_part_time_per IS NULL THEN
1098 l_part_time_per:=1;
1099 END IF;
1100 
1101     RETURN l_part_time_per;
1102  EXCEPTION
1103     when others then
1104     --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1105     IF org_hierarchy%ISOPEN THEN
1106       CLOSE org_hierarchy;
1107     END IF;
1108     RETURN 1;
1109  END Get_Part_Time_Perc_Method;
1110 
1111 -- Function which returns lunar 5-week month wage method for the given organization
1112 -- If the value is not specified for the given organization it performs the tree walk.
1113 
1117     --Determine the Organization Id of the Employees Assignment
1114     FUNCTION Get_Lunar_5_Week_Method
1115     (p_assignment_id NUMBER) RETURN NUMBER IS
1116     --
1118     --
1119     CURSOR get_org_id(p_assignment_id number) is
1120     select paa.organization_id
1121     from per_all_assignments_f paa,fnd_sessions ses
1122     where paa.assignment_id = p_assignment_id and
1123     ses.effective_date between paa.effective_start_date and paa.effective_end_date and
1124     session_id = userenv('sessionid');
1125 
1126     --
1127     --Cursor which fetches lunar 5 week month wage method for the given HR Organization
1128     --
1129     CURSOR Lunar_5_Week_Month_Wage_Method
1130     (l_org_id in hr_organization_units.organization_id%type) IS
1131      select
1132      e.org_information_id,
1133      e.org_information9 Lunar_5_Week_Month_Wage_Method
1134      from
1135      hr_organization_information e
1136      where
1137      e.organization_id=l_org_id and
1138      e.org_information_context= 'NL_ORG_INFORMATION'
1139      and e.org_information9 IS NOT NULL;
1140     --
1141     --Local Variables
1142     --
1143     l_lunar_method        Number;
1144     v_lunar_method        Lunar_5_Week_Month_Wage_Method%ROWTYPE;
1145     l_org_id            per_all_assignments_f.organization_id%TYPE;
1146     l_organization_id   hr_organization_units.organization_id%TYPE;
1147     l_level             number;
1148 
1149  BEGIN
1150     --
1151     --Determine the Organization Id of the Employees Assignment
1152     --
1153     OPEN get_org_id(p_assignment_id);
1154     FETCH get_org_id into l_org_id;
1155     CLOSE get_org_id;
1156 
1157     l_lunar_method := Null;
1158     --
1159     --Check whether the lunar 5-week month wage method is specified for the Organization
1160     --
1161     OPEN Lunar_5_Week_Month_Wage_Method(l_org_id);
1162     Fetch Lunar_5_Week_Month_Wage_Method into v_lunar_method;
1163     If Lunar_5_Week_Month_Wage_Method%FOUND and v_lunar_method.Lunar_5_Week_Month_Wage_Method is not null then
1164     l_lunar_method:= v_lunar_method.Lunar_5_Week_Month_Wage_Method;
1165     End if;
1166     Close Lunar_5_Week_Month_Wage_Method;
1167 
1168     --If the lunar 5 week month wage method is not specified tree walk to find the organization with
1169     --the same value defined.
1170     --
1171     IF l_lunar_method IS NULL THEN
1172 
1173     if org_hierarchy%ISOPEN then
1174     CLOSE org_hierarchy;
1175     END IF;
1176 
1177     OPEN org_hierarchy(l_org_id);
1178     LOOP
1179         FETCH org_hierarchy into l_organization_id,l_level;
1180         exit when org_hierarchy%NOTFOUND or l_lunar_method IS NOT NULL;
1181         --
1182         --Fetch the Part Time Percetage Method for the given organization
1183         --
1184         open Lunar_5_Week_Month_Wage_Method(l_organization_id);
1185         FETCH Lunar_5_Week_Month_Wage_Method into v_lunar_method;
1186         if Lunar_5_Week_Month_Wage_Method%found and v_lunar_method.Lunar_5_Week_Month_Wage_Method is not null then
1187         l_lunar_method:= v_lunar_method.Lunar_5_Week_Month_Wage_Method;
1188         end if;
1189         close Lunar_5_Week_Month_Wage_Method;
1190     END LOOP;
1191     close org_hierarchy;
1192 
1193     END IF;
1194     IF l_lunar_method IS NULL THEN
1195     l_lunar_method:=0;
1196     END IF;
1197     RETURN l_lunar_method;
1198  EXCEPTION
1199     when others then
1200     --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1201     IF org_hierarchy%ISOPEN THEN
1202       CLOSE org_hierarchy;
1203     END IF;
1204     RETURN 0;
1205  END Get_Lunar_5_Week_Method;
1206 
1207  -- Start NL_Proration
1208 
1209  FUNCTION Get_Proration_Tax_Table
1210         (p_assignment_id number) RETURN Varchar2 IS
1211         --
1212         --Determine the Organization Id of the Employees Assignment
1213         --
1214         CURSOR get_org_id(p_assignment_id number) is
1215         select paa.organization_id
1216         from per_all_assignments_f paa,fnd_sessions ses
1217         where paa.assignment_id = p_assignment_id and
1218         ses.effective_date between paa.effective_start_date
1219         and paa.effective_end_date and
1220         session_id = userenv('sessionid');
1221 
1222         --
1223         --
1224 
1225         CURSOR cur_Pro_Tax_Table
1226         (l_org_id in hr_organization_units.organization_id%type) IS
1227          select
1228          e.org_information_id,
1229          e.org_information10 Proration_Tax_Table
1230          from
1231          hr_organization_information e
1232          where
1233          e.organization_id=l_org_id and
1234          e.org_information_context= 'NL_ORG_INFORMATION'
1235          and e.org_information10 IS NOT NULL;
1236         --
1237         --Local Variables
1238         --
1239         l_Pro_Tax_Table         hr_organization_information.ORG_INFORMATION10%TYPE;
1240     v_Pro_Tax_Table         cur_Pro_Tax_Table%ROWTYPE;
1241         l_org_id            per_all_assignments_f.organization_id%TYPE;
1242         l_organization_id       hr_organization_units.organization_id%TYPE;
1243         l_level                 number;
1244 
1245  BEGIN
1246         --
1247         --
1248      --
1249      --Determine the Organization Id of the Employees Assignment
1250      --
1251      OPEN get_org_id(p_assignment_id);
1252      FETCH get_org_id into l_org_id;
1253      CLOSE get_org_id;
1254 
1255         l_Pro_Tax_Table:= Null;
1256         --
1257         --Check whether the Period_type is specified for the Organization
1258         --
1259         OPEN cur_Pro_Tax_Table (l_org_id);
1260         Fetch cur_Pro_Tax_Table into v_Pro_Tax_Table;
1264         End if;
1261         If cur_Pro_Tax_Table%FOUND and
1262            v_Pro_Tax_Table.Proration_Tax_Table is not null then
1263         l_Pro_Tax_Table:= v_Pro_Tax_Table.Proration_Tax_Table;
1265         Close cur_Pro_Tax_Table;
1266 
1267         hr_utility.trace('l_Pro_Tax_Table is : '||l_Pro_Tax_Table);
1268 
1269         --If the Working_hours_Per_Week is not specified tree walk
1270         --to find the organization with
1271         --the same value defined.
1272         --
1273         IF l_Pro_Tax_Table IS NULL THEN
1274 
1275         if org_hierarchy%ISOPEN then
1276             CLOSE org_hierarchy;
1277         END IF;
1278 
1279         OPEN org_hierarchy(l_org_id);
1280         LOOP
1281         FETCH org_hierarchy into l_organization_id,l_level;
1282         exit when org_hierarchy%NOTFOUND or l_Pro_Tax_Table IS NOT NULL;
1283         --
1284         --
1285         OPEN Cur_Pro_Tax_Table(l_organization_id);
1286         Fetch Cur_Pro_Tax_Table into v_Pro_Tax_Table;
1287         If Cur_Pro_Tax_Table%FOUND and
1288           v_Pro_Tax_Table.Proration_Tax_Table is not null then
1289             l_Pro_Tax_Table:= v_Pro_Tax_Table.Proration_Tax_Table;
1290         end if;
1291         Close Cur_Pro_Tax_Table;
1292         END LOOP;
1293         close org_hierarchy;
1294 
1295         END IF;
1296     --If the value for Proration Tax Table is not specified anywhere
1297        --up in the hierarchy default it to 1
1298     IF l_Pro_Tax_Table IS NULL THEN
1299         l_Pro_Tax_Table :=1;
1300     END IF;
1301 
1302         RETURN l_Pro_Tax_Table;
1303  EXCEPTION
1304         when others then
1305         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1306         IF org_hierarchy%ISOPEN THEN
1307           CLOSE org_hierarchy;
1308         END IF;
1309         RETURN '0';
1310  END Get_Proration_Tax_Table;
1311 
1312 
1313  -- End NL_Proration
1314 
1315     -- Service function which returns the SI Provider information for the given organization.
1316     -- It performs tree walk if SI information is not defined for the given organization.
1317     --
1318 
1319     FUNCTION Get_ER_SI_Prov_HR_Org_ID
1320     (p_organization_id NUMBER,p_si_type VARCHAR2,p_assignment_id NUMBER) RETURN NUMBER IS
1321 
1322         l_proc            varchar2(72) := g_package || '.Get_SI_Provider_Info';
1323         l_provider_info   hr_organization_units.organization_id%type;
1324         l_org_id          hr_organization_units.organization_id%type;
1325 
1326 
1327         --
1328         -- Cursor which fetches Social Insurance Provider overridden at the Assignment Level
1329         -- ordering the records by the si class order (A record for a Individual SI type would be
1330         -- ordered higher than a AMI record).
1331         CURSOR asg_provider
1332         (l_org_id in hr_organization_units.organization_id%type,l_si_type varchar2,l_assgn_id NUMBER) IS
1333          select pae.aei_information8 provider,
1334          decode(pae.aei_information3,'AMI',0,1) si_class_order
1335          from per_assignment_extra_info pae
1336          ,fnd_sessions s
1337          where assignment_id = l_assgn_id
1338          and (pae.aei_information3=decode (l_si_type,'WEWE','WW','WEWA','WW',
1339                         'WAOB','WAO','WAOD','WAO','PRIVATE_HEALTH','ZFW',l_si_type) or
1340          pae.aei_information3 = DECODE(l_si_type,'WEWE','AMI','WEWA','AMI',
1341                         'WAOB','AMI','WAOD','AMI',
1342                         'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
1343                         'ZVW','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type))
1344         and s.effective_date between
1345         fnd_date.canonical_to_date(pae.aei_information1)
1346         and nvl(fnd_date.canonical_to_date(pae.aei_information2),s.effective_date) AND
1347         s.session_id=userenv('sessionid')
1348         order by si_class_order desc;
1349 
1350         --
1351         -- Cursor which fetches Social Insurance Provider for the given Hr Organization
1352         -- and which offers SI type ordering the records first by the Primary provider Flag
1353         -- and then by the si class order(A record for a Individual SI type would be
1354         -- ordered higher than a AMI record).
1355         CURSOR org_uwv_provider
1356         (l_org_id in hr_organization_units.organization_id%type,l_si_type varchar2) IS
1357          select
1358          e.org_information4 provider,nvl(e.org_information7,'N') p_flag,
1359          decode(e.org_information3,'AMI',0,1) si_class_order
1360          from
1361          hr_organization_information e
1362          ,fnd_sessions s
1363          where
1364          e.organization_id=l_org_id and
1365          e.org_information_context = 'NL_SIP' and
1366          (e.org_information3=DECODE(l_si_type,'WEWE','WW','WEWA','WW','WAOB','WAO','WAOD','WAO',
1367                              'PRIVATE_HEALTH','ZFW',l_si_type) or
1368          e.org_information3 = DECODE(l_si_type,'WEWE','AMI','WEWA','AMI','WAOB','AMI','WAOD','AMI',
1369                         'ZFW','AMI','PRIVATE_HEALTH','AMI','ZW','AMI',
1370                         'ZVW','AMI','WGA','AMI','IVA','AMI','UFO','AMI',l_si_type)) and
1371          s.effective_date between
1372            fnd_date.canonical_to_date(e.org_INFORMATION1)
1373            and nvl(fnd_date.canonical_to_date(e.org_INFORMATION2),s.effective_date) AND
1374          s.session_id=userenv('sessionid')
1375          order by p_flag desc,si_class_order desc;
1376 
1377         v_asg_provider      asg_provider%ROWTYPE;
1378         v_org_uwv_provider  org_uwv_provider%ROWTYPE;
1379         l_level             number;
1380         l_organization_id   hr_organization_units.organization_id%TYPE;
1381         l_uwv_found            boolean := false;
1385         /* Fetch Override Ins Provider at the Asg Level*/
1382         l_uwv_org_id         hr_organization_units.organization_id%TYPE;
1383         l_er_org_id         hr_organization_units.organization_id%TYPE;
1384      BEGIN
1386         OPEN asg_provider(p_organization_id,p_si_type,p_assignment_id);
1387         FETCH asg_provider INTO v_asg_provider;
1388         CLOSE asg_provider;
1389 
1390 
1391         /* If Ins Provider at the Asg Level is specified*/
1392         IF v_asg_provider.provider IS NOT NULL THEN
1393            l_uwv_org_id := v_asg_provider.provider;
1394            l_er_org_id  := p_organization_id;
1395            --hr_utility.set_location('Asg Level UWV Prov l_uwv_org_id'||l_uwv_org_id,100);
1396         ELSE
1397             /* If Ins Provider at the Asg Level is not specified
1398             tree walk to find the Primary Insurance Provider at the level */
1399             --hr_utility.set_location('Calling Get_SI_Org_Id',200);
1400 
1401             l_uwv_found := FALSE;
1402             l_uwv_org_id := -1;
1403             l_er_org_id := -1;
1404             if org_hierarchy%ISOPEN then
1405                 CLOSE org_hierarchy;
1406             END IF;
1407             /*Start looking for the UWV Provider beginning from the HR Org
1408             of Employee */
1409 
1410             OPEN org_hierarchy(p_organization_id);
1411             LOOP
1412                 FETCH org_hierarchy into l_organization_id,l_level;
1413                 exit when org_hierarchy%NOTFOUND or l_uwv_found =TRUE ;
1414                 --hr_utility.set_location(' l_organization_id'||l_organization_id||' level '||l_level,300);
1415                 --Fetch UWV Provider assigned to the HR Organization
1416                 open org_uwv_provider(l_organization_id,p_si_type);
1417                 FETCH org_uwv_provider into v_org_uwv_provider;
1418                 if org_uwv_provider%found then
1419                     --hr_utility.set_location(' l_organization_id'||l_organization_id||' p_organization_id '||p_organization_id,310);
1420                     if l_organization_id =p_organization_id then
1421                         /*Assign the UWV Provider defined at the HR Org
1422                         But continue further to see if any Primary
1423                         UWV exists up in the hierarchy*/
1424                         l_uwv_org_id := v_org_uwv_provider.provider;
1425                         l_er_org_id  := l_organization_id;
1426                         --hr_utility.set_location(' Assign -HR Org l_uwv_org_id'||l_uwv_org_id,320);
1427                     else
1428                         /*Assign the UWV Provider defined at the Parent HR Org
1429                         if not overridden at the HR Org Level*/
1430                         if l_uwv_org_id =-1 then
1431                             l_uwv_org_id := v_org_uwv_provider.provider;
1432                             l_er_org_id  := l_organization_id;
1433                             --hr_utility.set_location(' Parent HR Org l_uwv_org_id'||l_uwv_org_id,330);
1434                         end if;
1435                     end if;
1436                     /*Check If the UWV Provider assigned is also the Primary
1437                      Quit Searching the hierarchy*/
1438                     if v_org_uwv_provider.p_flag='Y' then
1439                         l_uwv_found:=TRUE;
1440                         l_uwv_org_id := v_org_uwv_provider.provider;
1441                         l_er_org_id  := l_organization_id;
1442                         --hr_utility.set_location(' Primary UWV l_uwv_org_id'||l_uwv_org_id||' @ '||l_organization_id,340);
1443                     end if;
1444 
1445                 end if;
1446                 close org_uwv_provider;
1447             END LOOP;
1448             close org_hierarchy;
1449             --hr_utility.set_location(' UWV From Hierarchy l_uwv_org_id'||l_uwv_org_id,350);
1450 
1451         END IF;
1452         hr_utility.set_location(' UWV ID -> l_uwv_org_id'||l_uwv_org_id,360);
1453         hr_utility.set_location('ER UWV ID -> l_er_org_id'||l_er_org_id,360);
1454         RETURN l_er_org_id;
1455      EXCEPTION
1456         when others then
1457         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1458         IF org_hierarchy%ISOPEN THEN
1459           CLOSE org_hierarchy;
1460         END IF;
1461         RETURN -1;
1462      END Get_ER_SI_Prov_HR_Org_ID;
1463 
1464 
1465 -- To get all the employers for given Org Struct Version ID
1466 function Get_Employers_List(p_Org_Struct_Version_Id in number,
1467                             p_top_org_id in number,
1468                             p_sub_emp in varchar2)
1469 return varchar2 is
1470 
1471     cursor c_all_emp is
1472     select pose.organization_id_child employer
1473     from per_org_structure_elements pose,hr_organization_information e
1474     where 1=1 --pose.org_structure_version_id = P_Org_Struct_Version_Id --16275108
1475     and e.organization_id=pose.organization_id_child
1476     and ((e.org_information_context= 'NL_ORG_INFORMATION'
1477     and e.org_information3 IS NOT NULL
1478     and e.org_information4 IS NOT NULL)
1479     or (e.org_information_context= 'NL_LE_TAX_DETAILS'
1480     and e.org_information1 IS NOT NULL
1481     and e.org_information2 IS NOT NULL))
1482     start with pose.organization_id_parent = p_top_org_id
1483     connect by prior pose.organization_id_child = pose.organization_id_parent
1484     and pose.org_structure_version_id = p_Org_Struct_Version_Id
1485     union
1486     select to_number(p_top_org_id) employer from dual;
1487 
1488     emp_list varchar2(1000);
1489 
1490 begin
1491     if ((P_SUB_EMP='N') or (P_SUB_EMP is null)) then
1492         emp_list := p_top_org_id;
1493     else
1494     for i in c_all_emp
1495     loop
1496         if emp_list is not null then
1500         end if;
1497             emp_list:=emp_list||','||i.employer;
1498         else
1499             emp_list:=i.employer;
1501     end loop;
1502     END if;
1503     return '('||emp_list||')';
1504 
1505 end Get_Employers_List;
1506 
1507 -- Function which returns parental leave wage percentage for the given organization
1508 -- If the value is not specified for the given organization it performs the tree walk.
1509 FUNCTION Get_Parental_Leave_Wage_Perc(p_assignment_id NUMBER) RETURN NUMBER IS
1510     --
1511     --Determine the Organization Id of the Employees Assignment
1512     --
1513     CURSOR get_org_id(p_assignment_id number) is
1514     select paa.organization_id
1515     from per_all_assignments_f paa,fnd_sessions ses
1516     where paa.assignment_id = p_assignment_id and
1517     ses.effective_date between paa.effective_start_date and paa.effective_end_date and
1518     session_id = userenv('sessionid');
1519 
1520     --
1521     --Cursor which fetches Tax Information for the given HR Organization
1522     --
1523     CURSOR csr_Parental_Leave_Perc
1524     (l_org_id in hr_organization_units.organization_id%type) IS
1525      select
1526      e.org_information_id,
1527      e.org_information11 Parental_Leave_Perc
1528      from
1529      hr_organization_information e
1530      where
1531      e.organization_id=l_org_id and
1532      e.org_information_context= 'NL_ORG_INFORMATION'
1533      and e.org_information11 IS NOT NULL;
1534     --
1535     --Local Variables
1536     --
1537     l_parental_leave_perc        Number;
1538     v_csr_par_leave             csr_Parental_Leave_Perc%ROWTYPE;
1539     l_org_id                    per_all_assignments_f.organization_id%TYPE;
1540     l_organization_id           hr_organization_units.organization_id%TYPE;
1541     l_level                     number;
1542 
1543  BEGIN
1544     --
1545     --Determine the Organization Id of the Employees Assignment
1546     --
1547     OPEN get_org_id(p_assignment_id);
1548     FETCH get_org_id into l_org_id;
1549     CLOSE get_org_id;
1550 
1551     l_parental_leave_perc := Null;
1552     --
1553     --Check whether the Paid Parental Leave Percentage is specified for the Organization
1554     --
1555     OPEN csr_Parental_Leave_Perc(l_org_id);
1556     Fetch csr_Parental_Leave_Perc into v_csr_par_leave;
1557     If csr_Parental_Leave_Perc%FOUND and v_csr_par_leave.Parental_Leave_Perc is not null then
1558         l_parental_leave_perc:= v_csr_par_leave.Parental_Leave_Perc;
1559     End if;
1560     Close csr_Parental_Leave_Perc;
1561 
1562     --If the Paid Parental Leave Percentage is not specified tree walk to find
1563     --the organization with the  value defined.
1564     --
1565     IF l_parental_leave_perc IS NULL THEN
1566 
1567         if org_hierarchy%ISOPEN then
1568             CLOSE org_hierarchy;
1569         END IF;
1570 
1571         OPEN org_hierarchy(l_org_id);
1572         LOOP
1573             FETCH org_hierarchy into l_organization_id,l_level;
1574             exit when org_hierarchy%NOTFOUND or l_parental_leave_perc IS NOT NULL;
1575             --
1576             --Fetch the Parental Leave Percentage for the given organization
1577             --
1578             open csr_Parental_Leave_Perc(l_organization_id);
1579             FETCH csr_Parental_Leave_Perc into v_csr_par_leave;
1580             if csr_Parental_Leave_Perc%found and v_csr_par_leave.Parental_Leave_Perc is not null then
1581                 l_parental_leave_perc:= v_csr_par_leave.Parental_Leave_Perc;
1582             end if;
1583             close csr_Parental_Leave_Perc;
1584         END LOOP;
1585         close org_hierarchy;
1586 
1587     END IF;
1588     --If the value for Parental Leave Percentage is not specified anywhere up in the hierarchy default it to 0
1589     IF l_parental_leave_perc IS NULL THEN
1590         l_parental_leave_perc:=0;
1591     END IF;
1592 
1593     RETURN l_parental_leave_perc;
1594  EXCEPTION
1595     when others then
1596     --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1597     IF org_hierarchy%ISOPEN THEN
1598       CLOSE org_hierarchy;
1599     END IF;
1600     RETURN 0;
1601 
1602 END Get_Parental_Leave_Wage_Perc;
1603 
1604 -- Start CBS Reporting Frequency
1605 FUNCTION Get_Reporting_Frequency
1606         (p_org_id in hr_organization_units.organization_id%type) RETURN Varchar2 IS
1607         CURSOR csr_cbs_rep_freq
1608         (l_org_id in hr_organization_units.organization_id%type) IS
1609          select
1610          e.org_information_id,
1611          e.org_information15 cbs_reporting_frequency
1612          from
1613          hr_organization_information e
1614          where
1615          e.organization_id=l_org_id and
1616          e.org_information_context= 'NL_ORG_INFORMATION'
1617          and e.org_information15 IS NOT NULL;
1618         --
1619         --Local Variables
1620         --
1621         l_cbs_Rep_Freq          hr_organization_information.ORG_INFORMATION15%TYPE;
1622        v_Rep_Freq_Table           csr_cbs_rep_freq%ROWTYPE;
1623         l_org_id                per_all_assignments_f.organization_id%TYPE;
1624         l_organization_id       hr_organization_units.organization_id%TYPE;
1625         l_level                 number;
1626  BEGIN
1627         --
1628         --
1629          l_cbs_Rep_Freq  := Null;
1630         --
1631         --Check whether the Reporting_Frequency is specified for the Organization
1632         --
1633         OPEN csr_cbs_rep_freq (p_org_id);
1634         Fetch csr_cbs_rep_freq into v_Rep_Freq_Table ;
1635         If csr_cbs_rep_freq %FOUND and
1636            v_Rep_Freq_Table.cbs_reporting_frequency is not null then
1637         l_cbs_Rep_Freq:= v_Rep_Freq_Table.cbs_reporting_frequency;
1641         --If the Working_hours_Per_Week is not specified tree walk
1638         End if;
1639         Close csr_cbs_rep_freq;
1640         hr_utility.trace('l_cbs_Rep_Freq is : '||l_cbs_Rep_Freq);
1642         --to find the organization with
1643         --the same value defined.
1644         --
1645         IF l_cbs_Rep_Freq IS NULL THEN
1646         if org_hierarchy%ISOPEN then
1647             CLOSE org_hierarchy;
1648         END IF;
1649         OPEN org_hierarchy(p_org_id);
1650         LOOP
1651         FETCH org_hierarchy into l_organization_id,l_level;
1652         exit when org_hierarchy%NOTFOUND or l_cbs_Rep_Freq IS NOT NULL;
1653         --
1654         --
1655         OPEN csr_cbs_rep_freq(l_organization_id);
1656         Fetch csr_cbs_rep_freq into v_Rep_Freq_Table;
1657         If csr_cbs_rep_freq%FOUND and
1658           v_Rep_Freq_Table.cbs_reporting_frequency is not null then
1659             l_cbs_Rep_Freq:= v_Rep_Freq_Table.cbs_reporting_frequency;
1660         end if;
1661         Close csr_cbs_rep_freq;
1662         END LOOP;
1663         close org_hierarchy;
1664         END IF;
1665     --If the value for Proration Tax Table is not specified anywhere
1666        --up in the hierarchy default it to 1
1667     IF l_cbs_Rep_Freq IS NULL THEN
1668         l_cbs_Rep_Freq :=1;
1669     END IF;
1670         RETURN l_cbs_Rep_Freq;
1671  EXCEPTION
1672         when others then
1673         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1674         IF org_hierarchy%ISOPEN THEN
1675           CLOSE org_hierarchy;
1676         END IF;
1677         RETURN '0';
1678  END Get_Reporting_Frequency;
1679  --
1680  --
1681  -- Start Customer Number
1682  --
1683 FUNCTION Get_customer_number
1684         (p_org_id in hr_organization_units.organization_id%type) RETURN Varchar2 IS
1685         CURSOR csr_customer_number
1686         (l_org_id in hr_organization_units.organization_id%type) IS
1687          select
1688          e.org_information_id,
1689          e.org_information16 cbs_cust_number
1690          from
1691          hr_organization_information e
1692          where
1693          e.organization_id=l_org_id and
1694          e.org_information_context= 'NL_ORG_INFORMATION'
1695          and e.org_information16 IS NOT NULL;
1696         --
1697         --Local Variables
1698         --
1699         l_cbs_cust_num          hr_organization_information.ORG_INFORMATION16%TYPE;
1700     v_cust_num_table        csr_customer_number%ROWTYPE;
1701         l_org_id            per_all_assignments_f.organization_id%TYPE;
1702         l_organization_id       hr_organization_units.organization_id%TYPE;
1703         l_level                 number;
1704  BEGIN
1705         --
1706         --
1707          l_cbs_cust_num  := Null;
1708         --
1709         --Check whether the Reporting_Frequency is specified for the Organization
1710         --
1711         OPEN csr_customer_number (p_org_id);
1712         Fetch csr_customer_number into v_cust_num_table ;
1713         If csr_customer_number %FOUND and
1714            v_cust_num_table.cbs_cust_number is not null then
1715         l_cbs_cust_num:= v_cust_num_table.cbs_cust_number;
1716         End if;
1717         Close csr_customer_number;
1718         hr_utility.trace('l_cbs_cust_num is : '||l_cbs_cust_num);
1719         --If the Working_hours_Per_Week is not specified tree walk
1720         --to find the organization with
1721         --the same value defined.
1722         --
1723         IF l_cbs_cust_num IS NULL THEN
1724         if org_hierarchy%ISOPEN then
1725             CLOSE org_hierarchy;
1729         FETCH org_hierarchy into l_organization_id,l_level;
1726         END IF;
1727         OPEN org_hierarchy(p_org_id);
1728         LOOP
1730         exit when org_hierarchy%NOTFOUND or l_cbs_cust_num IS NOT NULL;
1731         --
1732         --
1733         OPEN csr_customer_number(l_organization_id);
1734         Fetch csr_customer_number into v_cust_num_table;
1735         If csr_customer_number%FOUND and
1736           v_cust_num_table.cbs_cust_number is not null then
1737             l_cbs_cust_num:= v_cust_num_table.cbs_cust_number;
1738         end if;
1739         Close csr_customer_number;
1740         END LOOP;
1741         close org_hierarchy;
1742         END IF;
1743         RETURN l_cbs_cust_num;
1744  EXCEPTION
1745         when others then
1746         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1747         IF org_hierarchy%ISOPEN THEN
1748           CLOSE org_hierarchy;
1749         END IF;
1750         RETURN 'Error';
1751  END Get_customer_number;
1752 --
1753 -- Start Company Unit
1754 --
1755 FUNCTION Get_company_unit
1756         (p_org_id in hr_organization_units.organization_id%type) RETURN Varchar2 IS
1757         CURSOR csr_company_unit
1758         (l_org_id in hr_organization_units.organization_id%type) IS
1759          select
1760          e.org_information_id,
1761          e.org_information18 cbs_company_unit
1762          from
1763          hr_organization_information e
1764          where
1765          e.organization_id=l_org_id and
1766          e.org_information_context= 'NL_ORG_INFORMATION'
1767          and e.org_information18 IS NOT NULL;
1768         --
1769         --Local Variables
1770         --
1771         l_cbs_company_unit         hr_organization_information.ORG_INFORMATION18%TYPE;
1772     v_company_unit_table        csr_company_unit%ROWTYPE;
1773         l_org_id            per_all_assignments_f.organization_id%TYPE;
1774         l_organization_id       hr_organization_units.organization_id%TYPE;
1775         l_level                 number;
1776  BEGIN
1777         --
1778         --
1779          l_cbs_company_unit  := Null;
1780         --
1781         --Check whether the Reporting_Frequency is specified for the Organization
1782         --
1783         OPEN csr_company_unit (p_org_id);
1784         Fetch csr_company_unit into v_company_unit_table ;
1785         If csr_company_unit %FOUND and
1786            v_company_unit_table.cbs_company_unit is not null then
1787         l_cbs_company_unit:= v_company_unit_table.cbs_company_unit;
1788         End if;
1789         Close csr_company_unit;
1790         hr_utility.trace('l_cbs_company_unit is : '||l_cbs_company_unit);
1791         --If the Working_hours_Per_Week is not specified tree walk
1792         --to find the organization with
1793         --the same value defined.
1794         --
1795         IF l_cbs_company_unit IS NULL THEN
1796         if org_hierarchy%ISOPEN then
1797             CLOSE org_hierarchy;
1798         END IF;
1799         OPEN org_hierarchy(p_org_id);
1800         LOOP
1801         FETCH org_hierarchy into l_organization_id,l_level;
1802         exit when org_hierarchy%NOTFOUND or l_cbs_company_unit IS NOT NULL;
1803         --
1804         --
1805         OPEN csr_company_unit(l_organization_id);
1806         Fetch csr_company_unit into v_company_unit_table;
1807         If csr_company_unit%FOUND and
1808           v_company_unit_table.cbs_company_unit is not null then
1809             l_cbs_company_unit:= v_company_unit_table.cbs_company_unit;
1810         end if;
1811         Close csr_company_unit;
1812         END LOOP;
1813         close org_hierarchy;
1814         END IF;
1815     --If the value for Company Unit is not specified anywhere
1816        --up in the hierarchy default it to 0
1817     IF l_cbs_company_unit IS NULL THEN
1818         l_cbs_company_unit := 0;
1819     END IF;
1820         RETURN l_cbs_company_unit;
1821  EXCEPTION
1822         when others then
1823         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1824         IF org_hierarchy%ISOPEN THEN
1825           CLOSE org_hierarchy;
1826         END IF;
1827         RETURN '0';
1828  END Get_company_unit;
1829 --
1830 -- Start Get_Public_Sector_Org
1831 FUNCTION Get_Public_Sector_Org
1832         (p_org_id in hr_organization_units.organization_id%type) RETURN Varchar2 IS
1833         CURSOR csr_public_sector_info
1834         (l_org_id in hr_organization_units.organization_id%type) IS
1835          select
1836          e.org_information_id,
1837          e.org_information17 cbs_public_sector_org
1838          from
1839          hr_organization_information e
1840          where
1841          e.organization_id=l_org_id and
1842          e.org_information_context= 'NL_ORG_INFORMATION'
1843          and e.org_information17 IS NOT NULL;
1844         --
1845         --Local Variables
1846         --
1847         l_cbs_public_sector         hr_organization_information.ORG_INFORMATION17%TYPE;
1848     v_public_sector_Table       csr_public_sector_info%ROWTYPE;
1849         l_org_id                per_all_assignments_f.organization_id%TYPE;
1850         l_organization_id           hr_organization_units.organization_id%TYPE;
1851         l_level                     number;
1852  BEGIN
1853         --
1854         --
1855          l_cbs_public_sector  := Null;
1856         --
1857         --Check whether the Public_Sector Information is specified for the Organization
1858         --
1859         OPEN csr_public_sector_info (p_org_id);
1860         Fetch csr_public_sector_info into v_public_sector_Table ;
1861         If csr_public_sector_info %FOUND and
1862            v_public_sector_Table.cbs_public_sector_org is not null then
1866         hr_utility.trace('l_cbs_Rep_Freq is : '||l_cbs_public_sector);
1863         l_cbs_public_sector:= v_public_sector_Table.cbs_public_sector_org;
1864         End if;
1865         Close csr_public_sector_info;
1867 
1868         --
1869         IF l_cbs_public_sector IS NULL THEN
1870         if org_hierarchy%ISOPEN then
1871             CLOSE org_hierarchy;
1872         END IF;
1873         OPEN org_hierarchy(p_org_id);
1874         LOOP
1875             FETCH org_hierarchy into l_organization_id,l_level;
1876             exit when org_hierarchy%NOTFOUND or l_cbs_public_sector IS NOT NULL;
1877             --
1878             --
1879             OPEN csr_public_sector_info(l_organization_id);
1880             Fetch csr_public_sector_info into v_public_sector_Table;
1881             If csr_public_sector_info%FOUND and
1882               v_public_sector_Table.cbs_public_sector_org is not null then
1883                 l_cbs_public_sector:= v_public_sector_Table.cbs_public_sector_org;
1884             end if;
1885             Close csr_public_sector_info;
1886         END LOOP;
1887         close org_hierarchy;
1888         END IF;
1889     --If the value for Proration Tax Table is not specified anywhere
1890        --up in the hierarchy default it to 1
1891     IF l_cbs_public_sector IS NULL THEN
1892         l_cbs_public_sector :=1;
1893     END IF;
1894         RETURN l_cbs_public_sector;
1895  EXCEPTION
1896         when others then
1897         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1898         IF org_hierarchy%ISOPEN THEN
1899           CLOSE org_hierarchy;
1900         END IF;
1901         RETURN '0';
1902  END Get_Public_Sector_Org;
1903 
1904 -- Function which returns Full Sickness Wage Paid Indicator for the given organization
1905 -- If the value is not specified for the given organization it performs the tree walk.
1906 FUNCTION Get_Full_Sickness_Wage_Paid
1907         (p_org_id in hr_organization_units.organization_id%type) RETURN Varchar2 IS
1908         CURSOR csr_full_wage_paid
1909         (l_org_id in hr_organization_units.organization_id%type) IS
1910          select
1911          e.org_information_id,
1912          e.org_information19 full_sick_wage_paid
1913          from
1914          hr_organization_information e
1915          where
1916          e.organization_id=l_org_id and
1917          e.org_information_context= 'NL_ORG_INFORMATION'
1918          and e.org_information19 IS NOT NULL;
1919         --
1920         --Local Variables
1921         --
1922         l_full_wage_paid         hr_organization_information.ORG_INFORMATION17%TYPE;
1923         v_full_sick_wage       csr_full_wage_paid%ROWTYPE;
1924         l_org_id                per_all_assignments_f.organization_id%TYPE;
1925         l_organization_id           hr_organization_units.organization_id%TYPE;
1926         l_level                     number;
1927  BEGIN
1928         --
1929         --
1930          l_full_wage_paid  := Null;
1931         --
1932         --Check whether the Full Sickness Wage Paid Indicator is specified for the Organization
1933         --
1934         OPEN csr_full_wage_paid (p_org_id);
1935         Fetch csr_full_wage_paid into v_full_sick_wage ;
1936         If csr_full_wage_paid %FOUND and
1937            v_full_sick_wage.full_sick_wage_paid is not null then
1938         l_full_wage_paid:= v_full_sick_wage.full_sick_wage_paid;
1939         End if;
1940         Close csr_full_wage_paid;
1941         hr_utility.trace('l_cbs_Rep_Freq is : '||l_full_wage_paid);
1942 
1943         --
1944         IF l_full_wage_paid IS NULL THEN
1945         if org_hierarchy%ISOPEN then
1946             CLOSE org_hierarchy;
1947         END IF;
1948         OPEN org_hierarchy(p_org_id);
1949         LOOP
1950         FETCH org_hierarchy into l_organization_id,l_level;
1951         exit when org_hierarchy%NOTFOUND or l_full_wage_paid IS NOT NULL;
1952         --
1953         --
1954         OPEN csr_full_wage_paid(l_organization_id);
1955         Fetch csr_full_wage_paid into v_full_sick_wage;
1956         If csr_full_wage_paid%FOUND and
1957           v_full_sick_wage.full_sick_wage_paid is not null then
1958             l_full_wage_paid:= v_full_sick_wage.full_sick_wage_paid;
1959         end if;
1960         Close csr_full_wage_paid;
1961         END LOOP;
1962         close org_hierarchy;
1963         END IF;
1964 
1965         RETURN l_full_wage_paid;
1966  EXCEPTION
1967         when others then
1968         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
1969         IF org_hierarchy%ISOPEN THEN
1970           CLOSE org_hierarchy;
1971         END IF;
1972         RETURN '0';
1973  END Get_Full_Sickness_Wage_Paid;
1974 
1975  --
1976 FUNCTION Get_IZA_Weekly_Full_Hours
1977         (p_assignment_id in NUMBER ) RETURN Varchar2 IS
1978     -- Determine the Organization Id of the Employees Assignment
1979     --
1980     CURSOR get_org_id(p_assignment_id number) is
1981     select paa.organization_id
1982     from per_all_assignments_f paa,fnd_sessions ses
1983     where paa.assignment_id = p_assignment_id and
1984     ses.effective_date between paa.effective_start_date and paa.effective_end_date and
1985     session_id = userenv('sessionid');
1986         CURSOR csr_IZA_Weekly_Hours
1987         (l_org_id in hr_organization_units.organization_id%type) IS
1988          select
1989          e.org_information_id,
1990          e.org_information20 IZA_Weekly_Hours
1991          from
1992          hr_organization_information e
1993          where
1994          e.organization_id=l_org_id and
1995          e.org_information_context= 'NL_ORG_INFORMATION'
1996          and e.org_information20 IS NOT NULL;
1997         --
1998         --Local Variables
1999         --
2003         l_organization_id       hr_organization_units.organization_id%TYPE;
2000         l_IZA_Weekly_Hours         hr_organization_information.ORG_INFORMATION20%TYPE;
2001         v_IZA_Weekly_Hours_table        csr_IZA_Weekly_Hours%ROWTYPE;
2002         l_org_id                per_all_assignments_f.organization_id%TYPE;
2004         l_level                 number;
2005  BEGIN
2006         --
2007          --Determine the Organization Id of the Employees Assignment
2008     --
2009     OPEN get_org_id(p_assignment_id);
2010     FETCH get_org_id into l_org_id;
2011     CLOSE get_org_id;
2012         --
2013          l_IZA_Weekly_Hours  := Null;
2014         --
2015         --Check whether the IZA_Weekly_Hours is specified for the Organization
2016         --
2017         OPEN csr_IZA_Weekly_Hours (l_org_id);
2018         Fetch csr_IZA_Weekly_Hours into v_IZA_Weekly_Hours_table ;
2019         If csr_IZA_Weekly_Hours %FOUND and
2020            v_IZA_Weekly_Hours_table.IZA_Weekly_Hours is not null then
2021         l_IZA_Weekly_Hours:= v_IZA_Weekly_Hours_table.IZA_Weekly_Hours;
2022         End if;
2023         Close csr_IZA_Weekly_Hours;
2024         hr_utility.trace('l_IZA_Weekly_Hours is : '||l_IZA_Weekly_Hours);
2025         --If the IZA_Weekly_Hours is not specified tree walk
2026         --to find the organization with
2027         --the same value defined.
2028         --
2029         IF l_IZA_Weekly_Hours IS NULL THEN
2030         if org_hierarchy%ISOPEN then
2031             CLOSE org_hierarchy;
2032         END IF;
2033         OPEN org_hierarchy(l_org_id);
2034         LOOP
2035         FETCH org_hierarchy into l_organization_id,l_level;
2036         exit when org_hierarchy%NOTFOUND or l_IZA_Weekly_Hours IS NOT NULL;
2037         --
2038         --
2039         OPEN csr_IZA_Weekly_Hours(l_organization_id);
2040         Fetch csr_IZA_Weekly_Hours into v_IZA_Weekly_Hours_table;
2041         If csr_IZA_Weekly_Hours %FOUND and
2042           v_IZA_Weekly_Hours_table.IZA_Weekly_Hours is not null then
2043             l_IZA_Weekly_Hours:= v_IZA_Weekly_Hours_table.IZA_Weekly_Hours;
2044         end if;
2045         Close csr_IZA_Weekly_Hours;
2046         END LOOP;
2047         close org_hierarchy;
2048         END IF;
2049     -- If the value for IZA_Weely_Hours is not specified anywhere
2050     -- up in the hierarchy default it to 36
2051     IF l_IZA_Weekly_Hours IS NULL THEN
2052         l_IZA_Weekly_Hours := 36;
2053     END IF;
2054         RETURN l_IZA_Weekly_Hours;
2055  EXCEPTION
2056         when others then
2057         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
2058         IF org_hierarchy%ISOPEN THEN
2059           CLOSE org_hierarchy;
2060         END IF;
2061         RETURN '0';
2062  END Get_IZA_Weekly_Full_Hours;
2063 
2064 -- Start Monthly Full time Hours
2065 FUNCTION Get_IZA_Monthly_Full_Hours
2066  (p_assignment_id in NUMBER ) RETURN Varchar2 IS
2067     -- Determine the Organization Id of the Employees Assignment
2068     --
2069     CURSOR get_org_id(p_assignment_id number) is
2070     select paa.organization_id
2071     from per_all_assignments_f paa,fnd_sessions ses
2072     where paa.assignment_id = p_assignment_id and
2073     ses.effective_date between paa.effective_start_date and paa.effective_end_date and
2074     session_id = userenv('sessionid');
2075     --
2076         CURSOR csr_IZA_Monthly_Hours
2077         (l_org_id in hr_organization_units.organization_id%type) IS
2078          select
2079          e.org_information_id,
2080          e.org_information12 IZA_Monthly_Hours
2081          from
2082          hr_organization_information e
2083          where
2084          e.organization_id=l_org_id and
2085          e.org_information_context= 'NL_ORG_INFORMATION'
2086          and e.org_information12 IS NOT NULL;
2087         --
2088         --Local Variables
2089         --
2090         l_IZA_Monthly_Hours         hr_organization_information.ORG_INFORMATION12%TYPE;
2091         v_IZA_Monthly_Hours_table        csr_IZA_Monthly_Hours%ROWTYPE;
2092         l_org_id                per_all_assignments_f.organization_id%TYPE;
2096         --
2093         l_organization_id       hr_organization_units.organization_id%TYPE;
2094         l_level                 number;
2095  BEGIN
2097         --Determine the Organization Id of the Employees Assignment
2098     --
2099     OPEN get_org_id(p_assignment_id);
2100     FETCH get_org_id into l_org_id;
2101     CLOSE get_org_id;
2102         --
2103          l_IZA_Monthly_Hours  := Null;
2104         --
2105         --Check whether the IZA_Monthly_Hours is specified for the Organization
2106         --
2107         OPEN csr_IZA_Monthly_Hours (l_org_id);
2108         Fetch csr_IZA_Monthly_Hours into v_IZA_Monthly_Hours_table ;
2109         If csr_IZA_Monthly_Hours %FOUND and
2110            v_IZA_Monthly_Hours_table.IZA_Monthly_Hours is not null then
2111         l_IZA_Monthly_Hours:= v_IZA_Monthly_Hours_table.IZA_Monthly_Hours;
2112         End if;
2113         Close csr_IZA_Monthly_Hours;
2114         hr_utility.trace('l_IZA_Monthly_Hours is : '||l_IZA_Monthly_Hours);
2115         --If the IZA_Monthly_Hours is not specified tree walk
2116         --to find the organization with
2117         --the same value defined.
2118         --
2119         IF l_IZA_Monthly_Hours IS NULL THEN
2120         if org_hierarchy%ISOPEN then
2121             CLOSE org_hierarchy;
2122         END IF;
2123         OPEN org_hierarchy(l_org_id);
2124         LOOP
2125         FETCH org_hierarchy into l_organization_id,l_level;
2126         exit when org_hierarchy%NOTFOUND or l_IZA_Monthly_Hours IS NOT NULL;
2127         --
2128         --
2129         OPEN csr_IZA_Monthly_Hours(l_organization_id);
2130         Fetch csr_IZA_Monthly_Hours into v_IZA_Monthly_Hours_table;
2131         If csr_IZA_Monthly_Hours %FOUND and
2132           v_IZA_Monthly_Hours_table.IZA_Monthly_Hours is not null then
2133             l_IZA_Monthly_Hours:= v_IZA_Monthly_Hours_table.IZA_Monthly_Hours;
2134         end if;
2135         Close csr_IZA_Monthly_Hours;
2136         END LOOP;
2137         close org_hierarchy;
2138         END IF;
2139     -- If the value for IZA_Weely_Hours is not specified anywhere
2140     -- up in the hierarchy default it to 36
2141     IF l_IZA_Monthly_Hours IS NULL THEN
2142         l_IZA_Monthly_Hours := 156;
2143     END IF;
2144         RETURN l_IZA_Monthly_Hours;
2145  EXCEPTION
2146         when others then
2147         --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
2148         IF org_hierarchy%ISOPEN THEN
2149           CLOSE org_hierarchy;
2150         END IF;
2151         RETURN '0';
2152  END Get_IZA_Monthly_Full_Hours;
2153 
2154 
2155  Function Get_IZA_Org_Id(p_org_structure_version_id NUMBER,p_organization_id NUMBER) RETURN NUMBER IS
2156      --
2157      -- Cursor which fetches IZA Information for the given HR Organization
2158      --
2159      CURSOR iza_organization
2160      (l_org_id in hr_organization_units.organization_id%type) IS
2161       select
2162       e.org_information_id,
2163       e.org_information1 iza_information
2164       from
2165       hr_organization_information e
2166       where
2167       e.organization_id=l_org_id and
2168       e.org_information_context= 'NL_IZA_REPO_INFO'
2169       and e.org_information1 IS NOT NULL
2173      --
2170       and e.org_information2 IS NOT NULL;
2171 
2172 
2174      -- Cursor which fetches IZA Organization list for the given HR Organization
2175      --
2176      CURSOR iza_org_hierarchy(l_org_struct_version_id in per_org_structure_versions.org_structure_version_id%type,
2177      l_org_id in hr_organization_units.organization_id%type) IS
2178      SELECT iza_org_id,lev from hr_organization_information e,(
2179          SELECT l_org_id iza_org_id,0 lev from dual
2180          UNION
2181          SELECT distinct organization_id_parent
2182                     ,level
2183              FROM per_org_structure_elements pose
2184               where   pose.org_structure_version_id = l_org_struct_version_id
2185          START WITH organization_id_child    = l_org_id
2186          CONNECT BY PRIOR organization_id_parent   = organization_id_child)
2187      where
2188      e.organization_id=iza_org_id and
2189      e.org_information_context= 'NL_IZA_REPO_INFO'
2190      and e.org_information1 IS NOT NULL
2191      and e.org_information2 IS NOT NULL
2192      ORDER BY lev;
2193 
2194      v_iza_org           iza_organization%ROWTYPE;
2195      l_level             number;
2196      l_iza_org_id         hr_organization_units.organization_id%TYPE;
2197 
2198  BEGIN
2199  l_iza_org_id := NULL;
2200 
2201      OPEN iza_organization(p_organization_id);
2202      Fetch iza_organization into v_iza_org;
2203      If iza_organization%FOUND and v_iza_org.iza_information is not null then
2204      l_iza_org_id:= p_organization_id;
2205      End if;
2206      Close iza_organization;
2207 
2208      if iza_org_hierarchy%ISOPEN then
2209      CLOSE iza_org_hierarchy;
2210      end if;
2211 
2212      /*Fetch the iza organization list with iza information defined beginning from the HR Org */
2213      if l_iza_org_id IS NULL then
2214      OPEN iza_org_hierarchy(p_org_structure_version_id,p_organization_id);
2215      FETCH iza_org_hierarchy into l_iza_org_id,l_level;
2216      close iza_org_hierarchy;
2217      end if;
2218 
2219      RETURN l_iza_org_id;
2220 
2221  EXCEPTION
2222  when others then
2223      --hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
2224      IF iza_org_hierarchy%ISOPEN THEN
2225        CLOSE iza_org_hierarchy;
2226      END IF;
2227  RETURN null;
2228  END Get_IZA_Org_Id;
2229 
2230      FUNCTION Get_SI_Provider_Excl_Info
2231         (p_organization_id NUMBER,p_si_class VARCHAR2,p_assignment_id NUMBER,p_date_earned DATE) RETURN NUMBER IS
2232 
2233         l_proc            varchar2(72) := g_package || '.Get_SI_Provider_Excl_Info';
2234         l_provider_info   hr_organization_units.organization_id%type;
2235         l_org_id          hr_organization_units.organization_id%type;
2236 
2237         -- Cursor which detects whether any Social Insurance type is excluded at the HR Org Level.
2238         CURSOR org_si_excluded
2239         (l_org_id in hr_organization_units.organization_id%type,l_si_class varchar2,l_date_earned DATE) IS
2240          select
2241          1
2242          from
2243          hr_organization_information e
2244          where e.organization_id=l_org_id
2245            and e.org_information_context = 'NL_AMI'
2246            and e.org_information3=l_si_class
2247            and l_date_earned between fnd_date.canonical_to_date(e.org_INFORMATION1)
2248                                 and nvl(fnd_date.canonical_to_date(e.org_INFORMATION2),hr_general.END_OF_TIME);
2249 
2250         v_org_si_excluded   org_si_excluded%ROWTYPE;
2251         l_level             number;
2252         l_organization_id   hr_organization_units.organization_id%TYPE;
2253         l_uwv_not_found        number;
2254 
2255      BEGIN
2256 
2257             l_uwv_not_found := 1;
2258             if org_hierarchy%ISOPEN then
2259                 CLOSE org_hierarchy;
2260             END IF;
2261             /*Start looking for the SI type being excluded beginning from the HR Org
2262             of Employee */
2263 
2264             OPEN org_hierarchy(p_organization_id);
2265             LOOP
2266                 FETCH org_hierarchy into l_organization_id,l_level;
2267                 exit when org_hierarchy%NOTFOUND or l_uwv_not_found = 0;
2268                 --hr_utility.set_location(' l_organization_id'||l_organization_id||' level '||l_level,300);
2269                 --Fetch UWV Provider assigned to the HR Organization
2270                 open org_si_excluded(l_organization_id,p_si_class,p_date_earned);
2271                 FETCH org_si_excluded into v_org_si_excluded;
2272                 if org_si_excluded%found then
2273                     --hr_utility.set_location(' l_organization_id'||l_organization_id||' p_organization_id '||p_organization_id,310);
2274                      /*** set the flag which states that this particular SI type is excluded at the HR ORG level ****/
2275                      l_uwv_not_found := 0;
2276                 end if;
2277                 close org_si_excluded;
2278             END LOOP;
2279             close org_hierarchy;
2280             --hr_utility.set_location(' UWV From Hierarchy l_uwv_org_id'||l_uwv_org_id,350);
2281 
2282         --END IF;
2283         --hr_utility.set_location(' UWV ID -> l_uwv_org_id'||l_uwv_org_id,360);
2284         RETURN l_uwv_not_found;
2285      EXCEPTION
2286         when others then
2287         hr_utility.set_location('Exception :' || l_proc||SQLERRM(SQLCODE),999);
2288         IF org_hierarchy%ISOPEN THEN
2292           CLOSE org_si_excluded;
2289           CLOSE org_hierarchy;
2290         END IF;
2291         IF org_si_excluded%ISOPEN THEN
2293         END IF;
2294         RETURN -1;
2295      END Get_SI_Provider_Excl_Info;
2296 
2297 
2298 FUNCTION Get_SI_Provider_Excl_Info
2299         (p_assignment_id NUMBER,p_si_class VARCHAR2,p_date_earned DATE) RETURN NUMBER IS
2300 
2301         --Determine the Organization Id of the Employees Assignment
2302         CURSOR get_org_id(p_assignment_id number) is
2303         select paa.organization_id
2304         from per_all_assignments_f paa,fnd_sessions ses
2305         where paa.assignment_id = p_assignment_id and
2306         ses.effective_date between paa.effective_start_date and paa.effective_end_date and
2307         session_id = userenv('sessionid');
2308 
2309         l_org_id per_all_assignments_f.organization_id%TYPE;
2310         l_excluded_ind NUMBER;
2311 
2312      BEGIN
2313 
2314         OPEN get_org_id(p_assignment_id);
2315         FETCH get_org_id into l_org_id;
2316         CLOSE get_org_id;
2317 
2318         l_excluded_ind := Get_SI_Provider_Excl_Info(l_org_id,p_si_class,p_assignment_id,p_date_earned);
2319 
2320         RETURN l_excluded_ind;
2321 
2322      END Get_SI_Provider_Excl_Info;
2323 
2324 --13959332
2325 FUNCTION get_lhd_proration_override(p_assignment_id NUMBER)
2326 RETURN VARCHAR2 IS
2327 --
2328 --Determine the Organization Id of the Employees Assignment
2329 --
2330 CURSOR csr_get_org_id(p_assignment_id NUMBER) IS
2331 SELECT  paa.organization_id
2332 FROM    per_all_assignments_f paa
2333        ,fnd_sessions ses
2334 WHERE   paa.assignment_id = p_assignment_id
2335 AND     ses.effective_date BETWEEN paa.effective_start_date
2336                            AND     paa.effective_end_date
2337 AND     session_id = userenv ('sessionid');
2338 
2339 CURSOR csr_get_lhd_override(l_org_id in hr_organization_units.organization_id%type) IS
2340 SELECT  hoi.org_information6 lhd_pro_override
2341 FROM    hr_organization_information hoi
2342 WHERE   hoi.organization_id = l_org_id
2343 AND     hoi.org_information_context = 'NL_ORG_INFORMATION'
2344 AND     hoi.org_information6 IS NOT NULL;
2345 --
2346 --Local Variables
2347 --
2348 v_csr_get_lhd_override     csr_get_lhd_override%ROWTYPE;
2349 l_lhd_pro_override         hr_organization_information.ORG_INFORMATION6%TYPE;
2350 l_org_id                   per_all_assignments_f.organization_id%TYPE;
2351 l_organization_id          per_all_assignments_f.organization_id%TYPE;  --15837938
2352 l_level             number;  --15837938
2353 
2354  BEGIN
2355 
2356  --
2357  --Determine the Organization Id of the Employees Assignment
2358  --
2359  OPEN csr_get_org_id(p_assignment_id);
2360  FETCH csr_get_org_id INTO l_org_id;
2361  CLOSE csr_get_org_id;
2362 
2363     l_lhd_pro_override:= 'N';
2364     --
2365     --Check whether the LHD Proration Override is specified for the Organization
2366     --
2367     OPEN csr_get_lhd_override (l_org_id);
2368     FETCH csr_get_lhd_override INTO v_csr_get_lhd_override;
2369        IF csr_get_lhd_override%FOUND AND v_csr_get_lhd_override.lhd_pro_override IS NOT NULL THEN
2370           l_lhd_pro_override:= v_csr_get_lhd_override.lhd_pro_override;
2371          CLOSE csr_get_lhd_override;
2372        ELSIF csr_get_lhd_override%NOTFOUND THEN
2373           IF csr_get_lhd_override%ISOPEN THEN
2374                  CLOSE csr_get_lhd_override;
2375            END IF;
2376            --Check the flag in organization hierarchy 15837938
2377            IF org_hierarchy%ISOPEN THEN
2378                 CLOSE org_hierarchy;
2379            END IF;
2380 
2381            --Walk through hierarchy from bottom to up
2382            OPEN org_hierarchy(l_org_id);
2383            LOOP
2384              FETCH org_hierarchy into l_organization_id,l_level;
2385              EXIT when org_hierarchy%NOTFOUND or l_lhd_pro_override ='Y' ;
2386              hr_utility.set_location(' l_organization_id'||l_organization_id||' level '||l_level,300);
2387              OPEN csr_get_lhd_override (l_organization_id);
2388              FETCH csr_get_lhd_override INTO v_csr_get_lhd_override;
2389              IF csr_get_lhd_override%FOUND AND v_csr_get_lhd_override.lhd_pro_override IS NOT NULL THEN
2390                  l_lhd_pro_override:= v_csr_get_lhd_override.lhd_pro_override;
2391              END IF;
2392              IF csr_get_lhd_override%ISOPEN THEN
2393                 CLOSE csr_get_lhd_override;
2394              END IF;
2395            END LOOP;
2396            IF org_hierarchy%ISOPEN THEN
2397                 CLOSE org_hierarchy;
2398            END IF;
2399        END IF;
2400 
2401     hr_utility.trace('LHD Proration Override is : '||l_lhd_pro_override);
2402 
2403  RETURN l_lhd_pro_override;
2404 
2405  EXCEPTION
2406    WHEN OTHERS THEN
2407    hr_utility.trace('Exception in get_lhd_proration_override' ||SQLERRM(SQLCODE));
2408    RETURN 'N';
2409 
2410 END get_lhd_proration_override;
2411 --13959332
2412 
2413 
2414 --13350181
2415   FUNCTION get_b_rule_separate_run
2416     (p_assignment_id IN number) RETURN varchar2 IS
2417 
2418     CURSOR csr_get_org_id(p_assignment_id IN number) IS
2419       SELECT  paa.organization_id
2420       FROM    per_all_assignments_f paa
2421               ,fnd_sessions ses
2422       WHERE   paa.assignment_id = p_assignment_id
2423       AND     ses.effective_date
2424               BETWEEN paa.effective_start_date
2425               AND     paa.effective_end_date
2426       AND     session_id = userenv ('sessionid');
2427 
2428     CURSOR csr_get_bene_rul_sepa(l_org_id IN hr_organization_units.organization_id%TYPE) IS
2429       SELECT  hoi.org_information7 benefi_rule
2430       FROM    hr_organization_information hoi
2431       WHERE   hoi.organization_id = l_org_id
2435   --Local Variable
2432       AND     hoi.org_information_context = 'NL_ORG_INFORMATION'
2433       AND     hoi.org_information7 IS NOT NULL;
2434 
2436     rec_get_bene_rul_sepa  csr_get_bene_rul_sepa%ROWTYPE;
2437     l_benefi_rule          hr_organization_information.org_information7%TYPE;
2438     l_org_id               per_all_assignments_f.organization_id%TYPE;
2439     l_organization_id      per_all_assignments_f.organization_id%TYPE;
2440     l_level                number;
2441 
2442   BEGIN
2443 
2444     OPEN csr_get_org_id (p_assignment_id);
2445     FETCH csr_get_org_id INTO l_org_id;
2446     CLOSE csr_get_org_id;
2447 
2448     l_benefi_rule := 'Y';
2449 
2450     OPEN csr_get_bene_rul_sepa (l_org_id);
2451     FETCH csr_get_bene_rul_sepa INTO rec_get_bene_rul_sepa;
2452 
2453     IF csr_get_bene_rul_sepa%FOUND AND rec_get_bene_rul_sepa.benefi_rule IS NOT NULL and rec_get_bene_rul_sepa.benefi_rule in ('Y','N') THEN
2454       l_benefi_rule := rec_get_bene_rul_sepa.benefi_rule;
2455       CLOSE csr_get_bene_rul_sepa;
2456     ELSIF csr_get_bene_rul_sepa%NOTFOUND THEN
2457 
2458     IF csr_get_bene_rul_sepa%ISOPEN THEN
2459                 CLOSE csr_get_bene_rul_sepa;
2460     END IF;
2461 
2462       IF org_hierarchy%ISOPEN THEN
2463         CLOSE org_hierarchy;
2464       END IF;
2465 
2466       OPEN org_hierarchy (l_org_id);
2467       LOOP
2468         FETCH org_hierarchy
2469           INTO    l_organization_id
2470                 , l_level;
2471         EXIT WHEN org_hierarchy%NOTFOUND
2472                   OR l_benefi_rule = 'Y';
2473 
2474         hr_utility.set_location (' l_organization_id'|| l_organization_id|| ' level '|| l_level, 300);
2475 
2476         OPEN csr_get_bene_rul_sepa (l_organization_id);
2477         FETCH csr_get_bene_rul_sepa  INTO    rec_get_bene_rul_sepa;
2478         IF csr_get_bene_rul_sepa%FOUND  AND rec_get_bene_rul_sepa.benefi_rule IS NOT NULL THEN
2479           l_benefi_rule := rec_get_bene_rul_sepa.benefi_rule;
2480         END IF;
2481         IF csr_get_bene_rul_sepa%ISOPEN THEN
2482           CLOSE csr_get_bene_rul_sepa;
2483         END IF;
2484       END LOOP;
2485       IF org_hierarchy%ISOPEN THEN
2486         CLOSE org_hierarchy;
2487       END IF;
2488     END IF;
2489 
2490 
2491     hr_utility.trace ('Beneficial Rule in Separate Run is : '|| l_benefi_rule);
2492 
2493     RETURN l_benefi_rule;
2494 
2495   EXCEPTION
2496     WHEN others THEN
2497       hr_utility.trace ('Exception in get_bene_rul_separate'|| sqlerrm (sqlcode));
2498       RETURN 'Y';
2499 
2500  END get_b_rule_separate_run;
2501 
2502 
2503 END HR_NL_ORG_INFO;