DBA Data[Home] [Help]

PACKAGE BODY: APPS.PAY_US_DEF_COMP_457

Source


1 Package Body pay_us_def_comp_457 as
2 /* $Header: py457rol.pkb 115.7 2002/12/31 22:33:21 tmehra ship $ */
3 --
4 -- ----------------------------------------------------------------------------+
5 -- |                     Private Global Definitions                           |
6 -- ----------------------------------------------------------------------------+
7 --
8 g_contr_type    varchar2(1)  := 'G'         ; -- Global Contr Type for 457
9 g_get_bal_flag  varchar2(7)  := 'CORRECT'             ;
10 g_package       varchar2(33) := 'pay_us_def_comp_457.'; -- Global Package Name
11 --
12 -- ----------------------------------------------------------------------------+
13 -- |                     Private Function called by Rollover_process
14 -- ----------------------------------------------------------------------------+
15 -- ----------------------------------------------------------------------------+
16 -- |------< Business_Rule_Proc >------|
17 -- ----------------------------------------------------------------------------+
18 -- Description
19 --   This procedure is used to report the records present in the
20 --   PAY_US_CONTRIBUTION_HISTORY table that are deviating the business
21 --   rules.
22 --
23 -- Pre Conditions
24 --   None.
25 --
26 -- In Parameters
27 --   p_person_id       Person Id for whom the data  has to be transferred.
28 --                     If person Id is null, then the program proceeds for
29 --                     for the whole GRE (Tax Unit)
30 --   p_year            Year (YYYY) for which the rollover has to run
31 --
32 -- Post Success
33 --   Processing continues
34 --
35 -- Post Failure
36 --   Errors handled by the procedure
37 --
38 -- Access Status
39 --   Internal table handler use only.
40 --
41 Procedure Business_Rule_Proc(p_year      IN NUMBER ,
42                              p_person_id IN NUMBER ,
43                              p_gre_id    IN NUMBER )
44 IS
45     l_proc               VARCHAR2(72) := g_package || 'Business_Rule_Proc';
46     l_full_name          per_people_f.full_name%TYPE;
47     l_person_id          NUMBER;
48     l_business_group_id  NUMBER;
49     l_max_contr_allowed  NUMBER;
50     l_amt_contr          NUMBER;
51     l_includable_comp    NUMBER;
52     TYPE l_rec_type IS RECORD
53     (
54         person_id           per_all_assignments_f.person_id%TYPE ,
55         business_group_id   NUMBER,
56         max_contr_allowed   NUMBER,
57         amt_contr           NUMBER,
58         includable_comp     NUMBER
59     );
60 
61     TYPE c_cursor_type1 IS REF CURSOR
62         RETURN l_rec_type;
63     Business_Rule_Proc_cur c_cursor_type1;
64 BEGIN
65     hr_utility.set_location('Entering:'||l_proc, 5);
66 
67 /* In the SQLs belwo the MAX(NVL(max_contr_allowed, 0)) = 0  OR
68    SUM(NVL(includable_comp, 0)) = 0) have been used, these are because it is a
69    kind of an exception. Includable comp should not be zero and as well
70    max contr allowed should not be 0. It indicates that function that
71    calculates these two values returned 0 */
72 
73     IF (p_person_id IS NULL AND p_gre_id IS NOT NULL) THEN
74 
75         OPEN Business_Rule_Proc_cur FOR
76             SELECT person_id                     ,
77                    business_group_id             ,
78                    MAX(NVL(max_contr_allowed, 0)),
79                    SUM(NVL(amt_contr, 0))        ,
80                    SUM(NVL(includable_comp, 0))
81             FROM   PAY_US_CONTRIBUTION_HISTORY
82             WHERE  TO_NUMBER(TO_CHAR(date_from, 'YYYY')) = p_year
83             AND    TO_NUMBER(TO_CHAR(date_to  , 'YYYY')) = p_year
84             AND    tax_unit_id                           = p_gre_id
85             GROUP BY person_id        ,
86                      business_group_id
87             HAVING (MAX(NVL(max_contr_allowed, 0)) < SUM(NVL(amt_contr, 0)) OR
88                     MAX(NVL(max_contr_allowed, 0)) = 0  OR
89                     SUM(NVL(includable_comp, 0))   = 0)      ;
90 
91     hr_utility.set_location('Opened cursor Business_Rule_Proc_cur' , 10);
92 
93     ELSIF (p_person_id IS NOT NULL AND p_gre_id IS NULL) THEN
94 
95         OPEN Business_Rule_Proc_cur FOR
96             SELECT person_id                     ,
97                    business_group_id             ,
98                    MAX(NVL(max_contr_allowed, 0)),
99                    SUM(NVL(amt_contr, 0))        ,
100                    SUM(NVL(includable_comp, 0))
101             FROM   PAY_US_CONTRIBUTION_HISTORY
102             WHERE  TO_NUMBER(TO_CHAR(date_from, 'YYYY')) = p_year
103             AND    TO_NUMBER(TO_CHAR(date_to  , 'YYYY')) = p_year
104             AND    person_id = p_person_id
105             GROUP BY person_id        ,
106                      business_group_id
107             HAVING (MAX(NVL(max_contr_allowed, 0)) < SUM(NVL(amt_contr, 0)) OR
108                     MAX(NVL(max_contr_allowed, 0)) = 0  OR
109                     SUM(NVL(includable_comp, 0))   = 0)                 ;
110 
111     hr_utility.set_location('Opened cursor Business_Rule_Proc_cur' , 11);
112 
113     ELSIF (p_person_id IS NOT NULL AND p_gre_id IS NOT NULL) THEN
114 
115         OPEN Business_Rule_Proc_cur FOR
116             SELECT person_id                     ,
117                    business_group_id             ,
118                    MAX(NVL(max_contr_allowed, 0)),
119                    SUM(NVL(amt_contr, 0))        ,
120                    SUM(NVL(includable_comp, 0))
121             FROM   PAY_US_CONTRIBUTION_HISTORY
122             WHERE  TO_NUMBER(TO_CHAR(date_from, 'YYYY')) = p_year
123             AND    TO_NUMBER(TO_CHAR(date_to  , 'YYYY')) = p_year
124             AND    person_id     = p_person_id
125             AND    tax_unit_id   = p_gre_id
126             GROUP BY person_id        ,
127                      business_group_id
128             HAVING (MAX(NVL(max_contr_allowed, 0)) < SUM(NVL(amt_contr, 0)) OR
129                     MAX(NVL(max_contr_allowed, 0)) = 0  OR
130                     SUM(NVL(includable_comp, 0))   = 0)                 ;
131 
132     hr_utility.set_location('Opened cursor Business_Rule_Proc_cur' , 12);
133 
134     END IF;
135 
136     LOOP
137     BEGIN
138         FETCH Business_Rule_Proc_cur INTO l_person_id        ,
139                                           l_business_group_id,
140                                           l_max_contr_allowed,
141                                           l_amt_contr        ,
142                                           l_includable_comp  ;
143         EXIT WHEN Business_Rule_Proc_cur%NOTFOUND;
144 -- EE
145         SELECT full_name
146         INTO   l_full_name
147         FROM   per_people_f      ppf,
148                per_person_types  ppt
149         WHERE  ppf.person_id = l_person_id
150         AND    ppf.effective_start_date =
151                        (SELECT MAX(a.effective_start_date)
152                         FROM   per_people_f     a,
153                                per_person_types b
154                         WHERE  TO_NUMBER(TO_CHAR(a.effective_start_date,'YYYY'))
155                                           <= p_year
156                         AND    TO_NUMBER(TO_CHAR(a.effective_end_date,'YYYY'))
157                                          >= p_year
158                         AND    a.person_id          = ppf.person_id
159                         AND    a.person_type_id     = b.person_type_id
160                         AND    a.business_group_id  = l_business_group_id
161                         AND    b.system_person_type = 'EMP' )
162         AND    ppf.business_group_id = l_business_group_id
163         AND    ppf.person_type_id      = ppt.person_type_id
164         AND    ppt.system_person_type  = 'EMP' ;
165 
166         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
167             FND_FILE.PUT_LINE(FND_FILE.LOG,'Person Id = ' ||
168             TO_CHAR(l_person_id) || ', Name = ' || l_full_name || ' has '
169             || 'contribution of ' || TO_CHAR(l_amt_contr) ||
170             ' Maximum contribution allowed for ' || ' for the Year = '
171            || TO_CHAR(p_year) || ' is ' || TO_CHAR(l_max_contr_allowed) ||
172            ' Includable Comp is ' || TO_CHAR(l_includable_comp) || ' in Business Group Id = ' || TO_CHAR(l_business_group_id));
173         ELSE
174             hr_utility.set_location('Person Id = ' ||
175             TO_CHAR(l_person_id) || ', Name = ' || l_full_name || ' has '
176             || 'contribution of ' || TO_CHAR(l_amt_contr) ||
177             ' Maximum contribution allowed for ' || ' for the Year = '
178            || TO_CHAR(p_year) || ' is ' || TO_CHAR(l_max_contr_allowed) ||
179            ' Includable Comp is ' || TO_CHAR(l_includable_comp) || ' in Business Group Id = ' || TO_CHAR(l_business_group_id), 15);
180         END IF;
181     EXCEPTION
182     WHEN OTHERS THEN
183         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
184             FND_FILE.PUT_LINE(FND_FILE.LOG,'Error occured in ' || l_proc
185            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE));
186         ELSE
187             hr_utility.set_location('Error occured ' || l_proc
188            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) , 15);
189         END IF;
190     END;
191     END LOOP;
192     CLOSE  Business_Rule_Proc_cur;
193     hr_utility.set_location('Leaving:'||l_proc, 999);
194 
195 EXCEPTION
196     WHEN OTHERS THEN
197         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
198             FND_FILE.PUT_LINE(FND_FILE.LOG,'Error occured in ' || l_proc
199            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE));
200         ELSE
201             hr_utility.set_location('Error occured ' || l_proc
202            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) , 15);
203         END IF;
204 END Business_Rule_Proc;
205 
206 -- ----------------------------------------------------------------------------+
207 -- |------< PAY_CONTRB_INS >------|
208 -- ----------------------------------------------------------------------------+
209 -- Description
210 --   This procedure is used to call the API that inserts data into the
211 --   PAY_US_CONTRIBUTION_HISTORY table
212 --+
213 -- Pre Conditions
214 --   None.
215 --+
216 -- In Parameters
217 --  l_business_group_id  Business Group Id
218 --  l_amt_contr          Amount contributed by the person
219 --  l_max_contr_allowed  Maximum contribution allowed for this person
220 --  l_includable_comp    Includable compensation for this person
221 --  l_tax_unit_id        Respective Government Reporting entity
222 --  l_person_id          Person Id for whom the data  has to be transferred.
223 --                       If person Id is null, then the program proceeds for
224 --                       for the whole GRE (Tax Unit)
225 --  l_year               Year (YYYY) for which the rollover has to run
226 -- Out Parameters
227 --  l_contr_history_id   The primary key value generated in
228 --                       PAY_US_CONTRIBUTION _HISTORY table
229 --  l_object_version_number The object_version_number generated in
230 --                       PAY_US_CONTRIBUTION _HISTORY table
231 --+
232 -- Post Success
233 --   Processing continues
234 --+
235 -- Post Failure
236 --   Errors handled by the procedure
237 --+
238 -- Access Status
239 --   Internal table handler use only.
240 --+
241 Procedure Pay_Contrb_Ins
242 (
243      l_business_group_id      IN  NUMBER  ,
244      l_amt_contr              IN  NUMBER  ,
245      l_max_contr_allowed      IN  NUMBER  ,
246      l_includable_comp        IN  NUMBER  ,
247      l_tax_unit_id            IN  NUMBER  ,
248      l_person_id              IN  NUMBER  ,
249      l_year                   IN  NUMBER  ,
250      l_contr_history_id       OUT NOCOPY NUMBER  ,
251      l_object_version_number  OUT NOCOPY NUMBER
252 ) IS
253     l_proc               VARCHAR2(72) := g_package || 'Pay_Contrb_Ins';
254 BEGIN
255     hr_utility.set_location('Entering:'||l_proc, 5);
256 
257     pay_contribution_history_api.create_contribution_history
258     (
259         p_validate                   => false                       ,
260         p_contr_history_id           => l_contr_history_id          ,
261         p_person_id                  => l_person_id                 ,
262         p_date_from                  => TO_DATE('01/01/' || to_char(l_year),
263                                          'DD/MM/YYYY'),
264         p_date_to                    => TO_DATE('31/12/' || to_char(l_year),
265                                          'DD/MM/YYYY'),
266         p_contr_type                 => g_contr_type                ,
267         p_business_group_id          => l_business_group_id         ,
268         p_legislation_code           => 'US'                        ,
269         p_amt_contr                  => l_amt_contr                 ,
270         p_max_contr_allowed          => l_max_contr_allowed         ,
271         p_includable_comp            => l_Includable_comp           ,
272         p_tax_unit_id                => l_tax_unit_id               ,
273         p_source_system              => 'PAY'                       ,
274         p_object_version_number      => l_object_version_number
275     );
276 
277     hr_utility.set_location('Leaving:'||l_proc, 1000);
278 
279 EXCEPTION
280     WHEN OTHERS THEN
281 
282      l_contr_history_id       := 0;
283      l_object_version_number  := 0;
284 
285         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
286             FND_FILE.PUT_LINE(FND_FILE.LOG,'Error occured while inserting in' ||
287             ' PAY_US_CONTRIBUTION_HISTORY table for Person id = ' ||
288             TO_CHAR(l_person_id) || ' GRE = ' || TO_CHAR(l_tax_unit_id)
289            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) ||
290               ' in ' || l_proc);
291         ELSE
292             hr_utility.set_location('Error occured while inserting in ' ||
293             ' PAY_US_CONTRIBUTION_HISTORY table for Person id = ' ||
294             TO_CHAR(l_person_id) || ' GRE = ' || TO_CHAR(l_tax_unit_id)
295            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) ||
296               ' in ' || l_proc, 15);
297         END IF;
298 END Pay_Contrb_Ins;
299 
300 -- ----------------------------------------------------------------------------+
301 -- |------< Pay_Contrb_Upd >------|
302 -- ----------------------------------------------------------------------------+
303 -- Description
304 --   This procedure is used to call the API that updates data into the
305 --   PAY_US_CONTRIBUTION_HISTORY table
306 --+
307 -- Pre Conditions
308 --   None.
309 --+
310 -- In Parameters
311 --  l_contr_history_id   The primary key value generated in
312 --                      PAY_US_CONTRIBUTION _HISTORY table
313 --  l_object_version_number The object_version_number generated in
314 --                      PAY_US_CONTRIBUTION _HISTORY table
315 --  l_amt_contr          Amount contributed by the person
316 --  l_max_contr_allowed  Maximum contribution allowed for this person
317 --  l_includable_comp    Includable compensation for this person
318 --+
319 -- Post Success
320 --   Processing continues
321 --+
322 -- Post Failure
323 --   Errors handled by the procedure
324 --+
325 -- Access Status
326 --   Internal table handler use only.
327 --+
328 Procedure Pay_Contrb_Upd
329 (
330      l_contr_history_id      IN  OUT NOCOPY NUMBER  ,
331      l_object_version_number IN  OUT NOCOPY NUMBER  ,
332      l_amt_contr             IN  NUMBER      ,
333      l_max_contr_allowed     IN  NUMBER      ,
334      l_includable_comp       IN  NUMBER
335 ) IS
336     l_proc               VARCHAR2(72) := g_package || 'Pay_Contrb_Upd';
337     l_history_id         NUMBER;
338     l_ovn                NUMBER;
339 BEGIN
340     hr_utility.set_location('Entering:'||l_proc, 5);
341 
342     l_history_id := l_contr_history_id;
343     l_ovn        := l_object_version_number;
344 
345     pay_contribution_history_api.update_contribution_history
346     (
347         p_validate              => false                   ,
348         p_contr_history_id      => l_contr_history_id      ,
349         p_amt_contr             => l_amt_contr             ,
350         p_max_contr_allowed     => l_max_contr_allowed     ,
351         p_includable_comp       => l_includable_comp       ,
352         p_object_version_number => l_object_version_number
353      );
354 
355     hr_utility.set_location('Leaving:'||l_proc, 1000);
356 
357 EXCEPTION
358     WHEN OTHERS THEN
359 
360     l_contr_history_id := l_history_id;
361     l_object_version_number := l_ovn;
362 
363         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
364             FND_FILE.PUT_LINE(FND_FILE.LOG,'Error occured while Updating in' ||
365             ' PAY_US_CONTRIBUTION_HISTORY table for Contr_history_id = ' ||
366             TO_CHAR(l_contr_history_id) || ' Object Version Number = ' ||
367             TO_CHAR(l_object_version_number)
368            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) ||
369               ' in ' || l_proc);
370         ELSE
371             hr_utility.set_location('Error occured while Updating in ' ||
372             ' PAY_US_CONTRIBUTION_HISTORY table for Contr_history_id = ' ||
373             TO_CHAR(l_contr_history_id) || ' Object Version Number = ' ||
374             TO_CHAR(l_object_version_number)
375            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) ||
376               ' in ' || l_proc, 15);
377         END IF;
378 END Pay_Contrb_Upd;
379 
380 -- ----------------------------------------------------------------------------+
381 -- |------< Get_bal >------|
382 -- ----------------------------------------------------------------------------+
383 -- Description
384 -- This procedure calulates the value of the respective balance for a
385 -- given assignment, dimension and date
386 -- Pre Conditions
387 --   None.
388 --+
389 -- In Parameters
390 --  p_effective_date The date for which balance amount has to be calculated
391 --  p_assignment_id  The assignment Id for which balance amount has to be
392 --+                  calculated
393 --  p_tax_unit_id    Respective Government Reporting entity
394 --  p_balance_name   Balance Name
395 --  p_dimension_name Dimension Name
396 --  p_business_group_id Business Group Id
397 --+
398 -- Post Success
399 --   Processing continues
400 --+
401 -- Post Failure
402 --   Errors handled by the procedure
403 --+
404 -- Access Status
405 --   Internal table handler use only.
406 --+
407 Function Get_bal
408 (
409      p_effective_date    IN DATE    ,
410      p_assignment_id     IN NUMBER  ,
411      p_tax_unit_id       IN NUMBER  ,
412      p_balance_name      IN VARCHAR ,
413      p_dimension_name    IN VARCHAR ,
414      p_business_group_id IN NUMBER
415 ) RETURN NUMBER IS
416     l_defined_balance_id NUMBER ;
417     l_balance            NUMBER ;
418     l_proc               VARCHAR2(72) := g_package || 'Get_bal';
419 BEGIN
420 
421     hr_utility.set_location('Entering:'||l_proc, 5);
422 
423     g_get_bal_flag := 'CORRECT';
424     pay_balance_pkg.set_context('tax_unit_id', p_tax_unit_id   );
425     pay_balance_pkg.set_context('date_earned', p_effective_date);
426 
427     IF (p_balance_name <> 'Def Comp 457'
428           AND p_balance_name <> 'Calc 457 Limit') THEN
429         SELECT  /*+ USE_NL (pbd) */
430                pdb.defined_balance_id
431         INTO   l_defined_balance_id
432         FROM   pay_balance_types      pbt ,
433                pay_defined_balances   pdb ,
434                pay_balance_dimensions pbd
435         WHERE  pbt.balance_name           = p_balance_name
436         AND    pbt.balance_type_id        = pdb.balance_type_id
437         AND    pbd.balance_dimension_id   = pdb.balance_dimension_id
438         AND    pbd.dimension_name         = p_dimension_name
439         AND    pdb.business_group_id      = p_business_group_id;
440     ELSE
441         SELECT  /*+ USE_NL (pbd) */
442                pdb.defined_balance_id
443         INTO   l_defined_balance_id
444         FROM   pay_balance_types      pbt ,
445                pay_defined_balances   pdb ,
446                pay_balance_dimensions pbd
447         WHERE  pbt.balance_name           = p_balance_name
448         AND    pbt.balance_type_id        = pdb.balance_type_id
449         AND    pbd.balance_dimension_id   = pdb.balance_dimension_id
450         AND    pbd.dimension_name         = p_dimension_name;
451     END IF;
452 
453     hr_utility.set_location('Balance = ' || p_balance_name || ' ' ||
454 TO_CHAR(l_defined_balance_id) || ' ' || TO_CHAR(p_assignment_id), 15);
455 
456     l_balance := NVL(pay_balance_pkg.get_value(l_defined_balance_id,
457                                                p_assignment_id    ,
458                                                p_effective_date ), 0);
459     hr_utility.set_location('Leaving:'||l_proc, 1000);
460 
461     RETURN l_balance;
462 EXCEPTION
463     WHEN NO_DATA_FOUND THEN
464         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
465             FND_FILE.PUT_LINE(FND_FILE.LOG,p_balance_name ||
466                ' not found for Assignment Id ' || TO_CHAR(p_assignment_id) ||
467               ' in ' || TO_CHAR(p_business_group_id) || ' ' || l_proc);
468         ELSE
469             hr_utility.set_location(p_balance_name ||
470                ' not found for Assignment Id ' || TO_CHAR(p_assignment_id) ||
471               ' in ' || l_proc, 10);
472         END IF;
473         g_get_bal_flag := 'ERROR';
474         RETURN 0;
475     WHEN OTHERS THEN
476         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
477             FND_FILE.PUT_LINE(FND_FILE.LOG,'Error occured while calculating ' ||
478            p_balance_name || ' for Assignment Id ' || TO_CHAR(p_assignment_id)
479            || SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) ||
480               ' in ' || l_proc);
481         ELSE
482             hr_utility.set_location('Error occured while calculating ' ||
483            p_balance_name || ' for Assignment Id ' || TO_CHAR(p_assignment_id)||
484             SUBSTR(SQLERRM, 1, 128) || ' ' || TO_CHAR(SQLCODE) || ' in '
485            || l_proc, 15);
486         END IF;
487         g_get_bal_flag := 'ERROR';
488         RETURN 0;
489 END Get_bal;
490 -- ----------------------------------------------------------------------------+
491 -- |------< person_exists >------|
492 -- ----------------------------------------------------------------------------+
493 --+
494 -- Description
495 --  This procedure is used to return contr_history_id and object_version_number
496 --  for a particular person and a tax unit Id in a particular year in
497 --  PAY_US_CONTRIBUTION_HISTORY table. If no record is present then the
498 --  contr_history_id and object_version_number are 0.
499 --+
500 -- Pre Conditions
501 --   None.
502 --+
503 -- In Parameters
504 --   p_person_id       Person Id for whom the data  has to be transferred.
505 --   p_tax_unit_id     Respective Tax Unit Id
506 --   p_year            Year (YYYY) for which the rollover has to run
507 --+
508 -- Out Parameters
509 --   p_contr_history_id  The contr_history_id in
510 --+                      PAY_US_CONTRIBUITON_HISTORY table
511 --   p_ovn_number        The object_version_number in
512 --                       PAY_US_CONTRIBUITON_HISTORY table
513 --+
514 -- Post Success
515 --   Processing continues
516 --+
517 -- Post Failure
518 --   Errors handled by the procedure
519 --+
520 -- Access Status
521 --   Internal table handler use only.
522 --+
523 PROCEDURE person_exists(p_person_id         IN NUMBER,
524                         p_tax_unit_id       IN NUMBER,
525                         p_year              IN NUMBER,
526                         p_contr_history_id OUT NOCOPY NUMBER,
527                         p_ovn_number       OUT NOCOPY NUMBER,
528                         p_business_group_id IN NUMBER ) IS
529     l_contr_history_id NUMBER       := 0;
530     l_proc             VARCHAR2(72) := g_package || 'person_exists';
531 BEGIN
532     hr_utility.set_location('Entering:'||l_proc, 5);
533 
534     SELECT contr_history_id ,
535            object_version_number
536     INTO   p_contr_history_id,
537            p_ovn_number
538     FROM   PAY_US_CONTRIBUTION_HISTORY
539     WHERE  CONTR_TYPE                            = g_contr_type
540     AND    TO_NUMBER(TO_CHAR(DATE_FROM, 'YYYY')) = p_year
541     AND    TO_NUMBER(TO_CHAR(DATE_TO, 'YYYY'))   = p_year
542     AND    tax_unit_id                           = p_tax_unit_id
543     AND    person_id                             = p_person_id
544     AND    business_group_id                     = p_business_group_id;
545 
546     hr_utility.set_location('Leaving:'||l_proc, 1000);
547 
548 EXCEPTION
549     WHEN NO_DATA_FOUND THEN
550         p_contr_history_id := 0;
551         p_ovn_number       := 0;
552     WHEN OTHERS THEN
553         p_contr_history_id := 0;
554         p_ovn_number       := 0;
555         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
556             FND_FILE.PUT_LINE(FND_FILE.LOG, 'Error occured in WHEN OTHER for
557 Person Id ' || TO_CHAR(p_person_id) || ' for Year = ' || TO_CHAR(p_year) ||
558 ' in ' || l_proc || SUBSTR(SQLERRM, 1, 128) || TO_CHAR(SQLCODE));
559         ELSE
560             hr_utility.set_location('Error occured in WHEN OTHER for Person Id '||
561 TO_CHAR(p_person_id) || ' for Year = ' || TO_CHAR(p_year) || ' in ' || l_proc ||
562 SUBSTR(SQLERRM, 1, 128) || TO_CHAR(SQLCODE), 10);
563         END IF;
564 END person_exists;
565 --
566 -- ----------------------------------------------------------------------------+
567 -- |                     Public Procedure                     |
568 -- ----------------------------------------------------------------------------+
569 --
570 -- ----------------------------------------------------------------------------+
571 -- |------< Rollover_process >------|
572 -- ----------------------------------------------------------------------------+
573 --+
574 -- Description
575 --   This procedure is used to find all the employees that have 457 element
576 --   associated with them. For all the employees that have 457 element
577 --   with them, this procedure, then called the function to calculate
578 --   the respective balances.
579 --+
580 -- Pre Conditions
581 --   None.
582 --+
583 -- In Parameters
584 --   p_gre_id          Respective Government Reporting entity
585 --   p_year            Year (YYYY) for which the rollover has to run
586 --   p_person_id       Person Id for whom the data  has to be transferred.
587 --                     If person Id is null, then the program proceeds for
588 --                     for the whole GRE (Tax Unit)
589 --   p_override_mode   If the mode is YES, then program updates the
590 --                     existing recs in PAY_US_CONTRIBUTION_HISTORY table, If it
591 --                     is NO, then it just inserts the new records
592 -- Out Parameters
593 --    errbuf           Returns the error buffer
594 --    retcode          Returns the error code
595 --+
596 -- Post Success
597 --   Processing continues
598 --+
599 -- Post Failure
600 --   Errors handled by the procedure
601 --+
602 -- Access Status
603 --   Internal table handler use only.
604 
605 Procedure rollover_process
606 (
607     errbuf            OUT  NOCOPY VARCHAR2               ,
608     retcode           OUT  NOCOPY NUMBER                 ,
609     p_year            IN   NUMBER                 ,
610     p_gre_id          IN   NUMBER    DEFAULT NULL ,
611     p_person_id       IN   NUMBER    DEFAULT NULL ,
612     p_override_mode   IN   VARCHAR2  DEFAULT 'NO'
613 ) IS
614     l_id                           NUMBER               ;
615     l_ovn                          NUMBER               ;
616     l_temp_person_id               NUMBER               ;
617     l_business_group_id            NUMBER               ;
618     l_contr_history_id             NUMBER       := 0    ;
619     l_ovn_number                   NUMBER       := 0    ;
620     l_tax_unit_id                  NUMBER       := 0    ;
621     l_Includable_comp              NUMBER       := 0    ;
622     l_Def_457_Contribution_balance NUMBER       := 0    ;
623     l_max_457_contrb_allowed       NUMBER       := 0    ;
624     l_person_id                    NUMBER       := 0    ;
625     l_assignment_id                NUMBER       := 0    ;
626 
627     l_element_name                 VARCHAR2(80) := ''   ;
628     l_element_information1         VARCHAR2(80) := ''   ;
629     l_full_name                    VARCHAR2(80) := ''   ;
630     l_statement                    VARCHAR2(3000) := '' ;
631     l_dimension                    VARCHAR2(80) := ''   ;
632     l_balance_name                 VARCHAR2(80) := ''   ;
633     l_override_mode                VARCHAR2(5)  := 'NO' ;
634     l_proc                         VARCHAR2(72) :=
635                                        g_package || 'rollover_process';
636     l_effective_date               DATE                 ;
637     l_old_effective_date           DATE                 ;
638 
639     l_first_time                   BOOLEAN      := TRUE ;
640     l_multiple_rec_flag            BOOLEAN      := FALSE;
641 
642 
643     TYPE t_get_bal_flag IS TABLE OF VARCHAR2(7) INDEX BY BINARY_INTEGER;
644     l_get_bal_flag t_get_bal_flag;
645 
646 -- The size of the table is chosen to be 7 as it will contain 'CORRECT' or
647 -- 'ERROR' or null
648 
649     TYPE c_cursor_type IS REF CURSOR
650         RETURN g_rec_type;
651     C_All_Emp c_cursor_type;
652 
653 BEGIN
654     hr_utility.set_location(' Entering:'||l_proc, 5);
655     l_get_bal_flag(1) := 'CORRECT';
656     l_get_bal_flag(2) := 'CORRECT';
657     l_get_bal_flag(3) := 'CORRECT';
658 
659     hr_api.mandatory_arg_error
660     (p_api_name       => l_proc   ,
661      p_argument       => 'p_year' ,
662      p_argument_value => p_year
663     );
664 
665 -- The call to proc above checks if p_year has been passed or not
666 
667     IF (p_person_id IS NULL) THEN
668     -- Check mandatory parameters have been set
669     -- This ensures that if person_id passed is null, then GRE has to be present
670         hr_api.mandatory_arg_error
671         (p_api_name       => l_proc     ,
672          p_argument       => 'p_gre_id' ,
673          p_argument_value => p_gre_id
674         );
675     END IF;
676 
677     hr_utility.set_location(' Deciding the cursor to be used', 10);
678 
679     IF (p_person_id IS NULL) THEN
680 
681         OPEN C_All_Emp FOR
682         SELECT   /*+ INDEX (pet  pay_element_types_f_pk)
683                      INDEX (pel  pay_element_links_f_n7)
684                      INDEX (ppt  per_person_types_pk)
685                      INDEX (hsck HR_SOFT_CODING_KEYFLEX_PK)
686                      USE_NL(hsck)  */
687                DISTINCT paa.person_id               ,
688                         TO_NUMBER(hsck.segment1)    ,
689                         pap.full_name               ,
690                         paa.assignment_id           ,
691                         pee.element_link_id         ,
692                         pet.element_name            ,
693                         paa.business_group_id       ,
694                         pet.element_information1    ,
695                         TO_CHAR(MAX(paa.effective_end_date), 'DD/MM/YYYY')
696         FROM            per_assignments_f           paa,
697                         per_all_people_f            pap,
698                         pay_element_entries_f       pee,
699                         pay_element_links_f         pel,
700                         pay_element_types_f         pet,
701                         per_person_types            ppt,
702                         hr_soft_coding_keyflex      hsck
703         WHERE paa.assignment_Type              = 'E'
704         AND   pap.person_id                    = paa.person_id
705         AND   pap.person_type_id               = ppt.person_Type_id
706         AND   ppt.system_person_type           = 'EMP'
707         AND   pee.assignment_id                = paa.assignment_id
708         AND   pee.element_link_id              = pel.element_link_id
709         AND   pet.element_information_Category = 'US_PRE-TAX DEDUCTIONS'
710         AND   pet.element_information1         = g_contr_type
711         AND   pet.element_type_id              = pel.element_type_id
712         AND   (TO_NUMBER(TO_CHAR(pap.effective_start_date,'YYYY')) <= p_year AND
713               TO_NUMBER(TO_CHAR(pap.effective_end_date,'YYYY'))   >= p_year    )
714         AND   (TO_NUMBER(TO_CHAR(paa.effective_start_date,'YYYY')) <= p_year AND
715               TO_NUMBER(TO_CHAR(paa.effective_end_date,'YYYY'))   >= p_year    )
716         AND   (TO_NUMBER(TO_CHAR(pee.effective_start_date,'YYYY')) <= p_year AND
717               TO_NUMBER(TO_CHAR(pee.effective_end_date,'YYYY'))   >= p_year    )
718         AND   (TO_NUMBER(TO_CHAR(pel.effective_start_date,'YYYY')) <= p_year AND
719               TO_NUMBER(TO_CHAR(pel.effective_end_date,'YYYY'))   >= p_year    )
720         AND   (TO_NUMBER(TO_CHAR(pet.effective_start_date,'YYYY')) <= p_year AND
721               TO_NUMBER(TO_CHAR(pet.effective_end_date,'YYYY'))   >= p_year    )
722         AND    pet.element_name NOT LIKE '%Special%'
723         AND    paa.soft_coding_keyflex_id   = hsck.soft_coding_keyflex_id
724         AND    TO_NUMBER(hsck.segment1)     = p_gre_id
725         AND    pap.effective_start_date     =
726                      (SELECT MAX(effective_start_date)
727                       FROM   per_all_people_f a,
728                              per_person_types b
729                       WHERE  a.person_type_id    = b.person_type_id
730                       AND    a.person_id         = pap.person_id
731                       AND    a.business_group_id = pap.business_group_id
732                       AND   (TO_NUMBER(TO_CHAR(pap.effective_start_date,'YYYY'))
733                                        <= p_year
734                       AND    TO_NUMBER(TO_CHAR(pap.effective_end_date,'YYYY'))
735                                        >= p_year    )
736                       AND    b.system_person_type = 'EMP')
737         GROUP BY paa.person_id               ,
738                  TO_NUMBER(hsck.segment1)    ,
739                  pap.full_name               ,
740                  paa.assignment_id           ,
741                  pee.element_link_id         ,
742                  pet.element_name            ,
743                  paa.business_group_id       ,
744                  pet.element_information1
745         ORDER  BY paa.person_id          ,
746                   paa.assignment_id      ,
747                   UPPER(pet.element_name) ;
748 
749     hr_utility.set_location(' Opened the cursor', 15);
750 
751     ELSIF (p_person_id IS NOT NULL AND p_gre_id IS NULL) THEN
752         OPEN  C_All_Emp FOR
753         SELECT DISTINCT paa.person_id               ,
754                         TO_NUMBER(hsck.segment1)    ,
755                         pap.full_name               ,
756                         paa.assignment_id           ,
757                         pee.element_link_id         ,
758                         pet.element_name            ,
759                         paa.business_group_id       ,
760                         pet.element_information1    ,
761                         TO_CHAR(MAX(paa.effective_end_date), 'DD/MM/YYYY')
762         FROM            per_assignments_f       paa,
763                         per_all_people_f            pap,
764                         pay_element_entries_f       pee,
765                         pay_element_links_f         pel,
766                         pay_element_types_f         pet,
767                         per_person_types            ppt,
768                         hr_soft_coding_keyflex      hsck
769         WHERE  paa.assignment_Type              = 'E'
770         AND    pap.person_id                    = paa.person_id
771         AND    pap.person_type_id               = ppt.person_Type_id
772         AND    ppt.system_person_type           = 'EMP'
773         AND    pee.assignment_id                = paa.assignment_id
774         AND    pel.element_type_id              = pet.element_type_id
775         AND    pee.element_link_id              = pel.element_link_id
776         AND    pet.element_information_Category = 'US_PRE-TAX DEDUCTIONS'
777         AND    pet.element_information1         = g_contr_Type
778         AND   (TO_NUMBER(TO_CHAR(pap.effective_start_date,'YYYY')) <= p_year AND
779               TO_NUMBER(TO_CHAR(pap.effective_end_date,'YYYY'))   >= p_year    )
780         AND   (TO_NUMBER(TO_CHAR(paa.effective_start_date,'YYYY')) <= p_year AND
781               TO_NUMBER(TO_CHAR(paa.effective_end_date,'YYYY'))   >= p_year    )
782         AND   (TO_NUMBER(TO_CHAR(pee.effective_start_date,'YYYY')) <= p_year AND
783               TO_NUMBER(TO_CHAR(pee.effective_end_date,'YYYY'))   >= p_year    )
784         AND   (TO_NUMBER(TO_CHAR(pel.effective_start_date,'YYYY')) <= p_year AND
785               TO_NUMBER(TO_CHAR(pel.effective_end_date,'YYYY'))   >= p_year    )
786         AND   (TO_NUMBER(TO_CHAR(pet.effective_start_date,'YYYY')) <= p_year AND
787               TO_NUMBER(TO_CHAR(pet.effective_end_date,'YYYY'))   >= p_year    )
788         AND    pet.element_name NOT LIKE '%Special%'
789         AND    pap.person_id                    = p_person_id
790         AND    paa.soft_coding_keyflex_id       = hsck.soft_coding_keyflex_id
791         AND    pap.effective_start_date         =
792                      (SELECT MAX(effective_start_date)
793                       FROM   per_all_people_f a,
794                              per_person_types b
795                       WHERE  a.person_type_id    = b.person_type_id
796                       AND    a.person_id         = pap.person_id
797                       AND    a.business_group_id = pap.business_group_id
798                       AND   (TO_NUMBER(TO_CHAR(pap.effective_start_date,'YYYY'))
799                                        <= p_year
800                       AND    TO_NUMBER(TO_CHAR(pap.effective_end_date,'YYYY'))
801                                        >= p_year    )
802                       AND    b.system_person_type = 'EMP')
803         GROUP BY paa.person_id               ,
804                  TO_NUMBER(hsck.segment1)    ,
805                  pap.full_name               ,
806                  paa.assignment_id           ,
807                  pee.element_link_id         ,
808                  pet.element_name            ,
809                  paa.business_group_id       ,
810                  pet.element_information1
811         ORDER  BY TO_NUMBER(hsck.segment1),
812                   paa.person_id           ,
813                   paa.assignment_id       ,
814                   UPPER(pet.element_name) ;
815 
816     hr_utility.set_location(' Opened the cursor', 15);
817 
818     ELSIF (p_person_id IS NOT NULL AND p_gre_id IS NOT NULL) THEN
819         OPEN C_ALL_Emp FOR
820         SELECT DISTINCT paa.person_id               ,
821                         TO_NUMBER(hsck.segment1)    ,
822                         pap.full_name               ,
823                         paa.assignment_id           ,
824                         pee.element_link_id         ,
825                         pet.element_name            ,
826                         paa.business_group_id       ,
827                         pet.element_information1    ,
828                         TO_CHAR(MAX(paa.effective_end_date), 'DD/MM/YYYY')
829         FROM            per_assignments_f       paa,
830                         per_all_people_f            pap,
831                         pay_element_entries_f       pee,
832                         pay_element_links_f         pel,
833                         pay_element_types_f         pet,
834                         per_person_types            ppt,
835                         hr_soft_coding_keyflex      hsck
836         WHERE paa.assignment_Type              = 'E'
837         AND   pap.person_id                    = paa.person_id
838         AND   pap.person_type_id               = ppt.person_Type_id
839         AND   ppt.system_person_type           = 'EMP'
840         AND   pee.assignment_id                = paa.assignment_id
841         AND   pel.element_type_id              = pet.element_type_id
842         AND   pee.element_link_id              = pel.element_link_id
843         AND   pet.element_information_Category = 'US_PRE-TAX DEDUCTIONS'
844         AND   pet.element_information1         = g_contr_Type
845         AND   (TO_NUMBER(TO_CHAR(pap.effective_start_date,'YYYY')) <= p_year AND
846               TO_NUMBER(TO_CHAR(pap.effective_end_date,'YYYY'))   >= p_year    )
847         AND   (TO_NUMBER(TO_CHAR(paa.effective_start_date,'YYYY')) <= p_year AND
848               TO_NUMBER(TO_CHAR(paa.effective_end_date,'YYYY'))   >= p_year    )
849         AND   (TO_NUMBER(TO_CHAR(pee.effective_start_date,'YYYY')) <= p_year AND
850               TO_NUMBER(TO_CHAR(pee.effective_end_date,'YYYY'))   >= p_year    )
851         AND   (TO_NUMBER(TO_CHAR(pel.effective_start_date,'YYYY')) <= p_year AND
852               TO_NUMBER(TO_CHAR(pel.effective_end_date,'YYYY'))   >= p_year    )
853         AND   (TO_NUMBER(TO_CHAR(pet.effective_start_date,'YYYY')) <= p_year AND
854               TO_NUMBER(TO_CHAR(pet.effective_end_date,'YYYY'))   >= p_year    )
855         AND    pet.element_name NOT LIKE '%Special%'
856         AND    pap.person_id                    = p_person_id
857         AND    paa.soft_coding_keyflex_id       = hsck.soft_coding_keyflex_id
858         AND    TO_NUMBER(hsck.segment1)         = p_gre_id
859         AND    pap.effective_start_date         =
860                      (SELECT MAX(effective_start_date)
861                       FROM   per_all_people_f a,
862                              per_person_types b
863                       WHERE  a.person_type_id    = b.person_type_id
864                       AND    a.person_id         = pap.person_id
865                       AND    a.business_group_id = pap.business_group_id
866                       AND   (TO_NUMBER(TO_CHAR(pap.effective_start_date,'YYYY'))
867                                        <= p_year
868                       AND    TO_NUMBER(TO_CHAR(pap.effective_end_date,'YYYY'))
869                                        >= p_year    )
870                       AND    b.system_person_type = 'EMP')
871         GROUP BY paa.person_id               ,
872                  TO_NUMBER(hsck.segment1)    ,
873                  pap.full_name               ,
874                  paa.assignment_id           ,
875                  pee.element_link_id         ,
876                  pet.element_name            ,
877                  paa.business_group_id       ,
878                  pet.element_information1
879         ORDER  BY TO_NUMBER(hsck.segment1),
880                   paa.person_id           ,
881                   paa.assignment_id       ,
882                   UPPER(pet.element_name) ;
883 
884     hr_utility.set_location(' Opened the cursor', 15);
885 
886     END IF;
887 
888     l_override_mode := UPPER(p_override_mode);
889     IF (l_override_mode = 'Y') THEN
890         l_override_mode := 'YES';
891     ELSE
892         l_override_mode := 'NO';
893     END IF;
894 
895 -- Defaults the override mode to 'NO'
896 
897  IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
898     FND_FILE.PUT_LINE(FND_FILE.LOG, 'Parameters received ---->     ' );
899     FND_FILE.PUT_LINE(FND_FILE.LOG, 'Person Id     : ' || TO_CHAR(p_person_id));
900     FND_FILE.PUT_LINE(FND_FILE.LOG, 'Year          : ' || TO_CHAR(p_year));
901     FND_FILE.PUT_LINE(FND_FILE.LOG, 'GRE           : ' || TO_CHAR(p_gre_id ));
902     FND_FILE.PUT_LINE(FND_FILE.LOG, 'Override Mode : ' || p_override_mode);
903   ELSE
904     hr_utility.set_location('Parameters received ---->     ' , 20);
905     hr_utility.set_location('Person Id     : ' || TO_CHAR(p_person_id), 25);
906     hr_utility.set_location('Year          : ' || TO_CHAR(p_year), 30);
907     hr_utility.set_location('GRE           : ' || TO_CHAR(p_gre_id ), 35);
908     hr_utility.set_location('Override Mode : ' || p_override_mode, 40);
909   END IF;
910 
911 
912     hr_utility.set_location('Fetching from C_All_Emp cursor ', 45);
913 
914     LOOP
915     BEGIN
916         FETCH C_All_Emp INTO g_old_rec;
917         l_get_bal_flag(1) := 'CORRECT';
918         l_get_bal_flag(2) := 'CORRECT';
919         l_get_bal_flag(3) := 'CORRECT';
920 
921         IF (TO_CHAR(l_old_effective_date,'DD/MM/YYYY') = '31/12/4712') THEN
922             l_effective_date := TO_DATE('31/12/' || p_year, 'DD/MM/YYYY');
923         ELSE
924             l_effective_date := l_old_effective_date;
925         END IF;
926 
927 -- The above IF statement takes care if the employee was terminated. Otherwise
928 -- if the emp is terminated and 31-DEC-YYYY is passed, then
929 -- pay_balance_pkg.get_value returns unhandled exception
930 
931         IF ((g_old_rec.person_id       = l_person_id      ) AND
932             (g_old_rec.tax_unit_id     = l_tax_unit_id    ) AND
933             (UPPER(g_old_rec.element_information1) =
934                            UPPER(l_element_information1)  ) AND
935             C_All_Emp%FOUND = TRUE                        )
936         THEN
937             hr_utility.set_location('Multiple Element IF', 50);
938 
939             IF (l_multiple_rec_flag = FALSE) THEN
940                 IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
941                     FND_FILE.PUT_LINE(FND_FILE.LOG,'Person Id = ' ||
942                         to_char(g_old_rec.person_id) || ', Name ' ||
943                         g_old_rec.full_name   ||
944              ' not selected as this person has multiple elements of same type');
945                 ELSE
946                     hr_utility.set_location('Person Id = ' ||
947                     TO_CHAR(g_old_rec.person_id) || ', Name ' ||
948                     g_old_rec.full_name   ||
949          ' not selected as this person has multiple elements of same type', 55);
950                 END IF;
951                 l_multiple_rec_flag := TRUE;
952 -- l_multiple_rec_flag = TRUE makes sure i the person has more than two 457
953 -- elements attached. The message above does not get printed more than once.
954             END IF;
955         ELSE
956 
957             hr_utility.set_location('Multiple Element ELSE ', 60);
958 
959             IF (l_multiple_rec_flag = FALSE AND l_first_time = FALSE) THEN
960 
961                 l_balance_name   :=  l_element_name || ' Eligible Comp';
962                 l_dimension      :=
963                      'Person within Government Reporting Entity Year to Date';
964 
965                 hr_utility.set_location('Calling Get_bal for ' ||
966                     l_balance_name, 65);
967 
968                 l_Includable_comp := NVL(Get_bal(
969                                         l_effective_date   ,
970                                         l_assignment_id    ,
971                                         l_tax_unit_id      ,
972                                         l_balance_name     ,
973                                         l_dimension        ,
974                                         l_business_group_id), 0);
975                 l_get_bal_flag(1)  := g_get_bal_flag;
976                 l_balance_name     :=  'Def Comp 457';
977                 l_dimension        :=
978                     'Person within Government Reporting Entity Year to Date';
979 
980                 hr_utility.set_location('Calling Get_bal for ' ||
981                    l_balance_name, 70);
982 
983                 l_Def_457_Contribution_balance := NVL(Get_bal(
984                                                          l_effective_date ,
985                                                          l_assignment_id  ,
986                                                          l_tax_unit_id    ,
987                                                          l_balance_name   ,
988                                                          l_dimension      ,
989                                                        l_business_group_id), 0);
990                 l_get_bal_flag(2)  := g_get_bal_flag;
991                 l_balance_name     := 'Calc 457 Limit';
992                 l_dimension        :=
993                     'Person within Government Reporting Entity Year to Date';
994 
995                 hr_utility.set_location('Calling Get_bal for ' ||
996                     l_balance_name, 75);
997 
998                 l_max_457_contrb_allowed := NVL(Get_bal( l_effective_date ,
999                                                          l_assignment_id  ,
1000                                                          l_tax_unit_id    ,
1001                                                          l_balance_name   ,
1002                                                          l_dimension      ,
1003                                                        l_business_group_id), 0);
1004                 l_get_bal_flag(3)  := g_get_bal_flag;
1005 
1006                 hr_utility.set_location('Calling person_Exists '
1007                       || TO_CHAR(l_person_id), 80);
1008 
1009                 person_exists(l_person_id        ,
1010                               l_tax_unit_id      ,
1011                               p_year             ,
1012                               l_contr_history_id ,
1013                               l_ovn_number       ,
1014                               l_business_group_id);
1015 
1016                 IF (l_contr_history_id = 0
1017                     AND (l_get_bal_flag(1) = 'CORRECT'   AND
1018                          l_get_bal_flag(2) = 'CORRECT'   AND
1019                          l_get_bal_flag(3) = 'CORRECT')) THEN
1020 
1021 -- l_get_bal_flag stores if the calls to Get_Bal proc were successful or not
1022 -- l_contr_history_id = 0 ensures that this person_id is not having a record
1023 -- for the partucular year
1024 
1025                     hr_utility.set_location('Inserting into PAY_US_CONTRIBUTION_HISTORY', 85);
1026                     Pay_Contrb_Ins(
1027                         l_business_group_id => l_business_group_id            ,
1028                         l_amt_contr         => l_Def_457_Contribution_balance ,
1029                         l_max_contr_allowed => l_max_457_contrb_allowed       ,
1030                         l_includable_comp   => l_Includable_comp              ,
1031                         l_tax_unit_id       => l_tax_unit_id                  ,
1032                         l_year              => p_year                         ,
1033                         l_person_id         => l_person_id                    ,
1034                         l_contr_history_id      => l_contr_history_id         ,
1035                         l_object_version_number => l_ovn_number              ) ;
1036 
1037 
1038                 ELSIF (l_contr_history_id <> 0        AND
1039                        l_contr_history_id IS NOT NULL AND
1040                        l_override_mode   = 'YES'      AND
1041                        l_get_bal_flag(1) = 'CORRECT'  AND
1042                        l_get_bal_flag(2) = 'CORRECT'  AND
1043                        l_get_bal_flag(3) = 'CORRECT') THEN
1044 
1045                     hr_utility.set_location('Updating PAY_US_CONTRIBUTION_HISTORY', 90);
1046                    Pay_contrb_Upd(
1047                       l_contr_history_id      => l_contr_history_id,
1048                       l_object_version_number => l_ovn_number      ,
1049                       l_amt_contr             => l_Def_457_Contribution_balance,
1050                       l_max_contr_allowed     => l_max_457_contrb_allowed     ,
1051                       l_includable_comp       => l_Includable_comp);
1052 
1053                 END IF;
1054             END IF;
1055             l_multiple_rec_flag := FALSE;
1056         END IF;
1057 
1058         hr_utility.set_location('Assigning g_old_rec values to the local variables ' , 95);
1059 
1060         l_person_id             := g_old_rec.person_id            ;
1061         l_assignment_id         := g_old_rec.assignment_id        ;
1062         l_element_name          := g_old_rec.element_name         ;
1063         l_element_information1  := g_old_rec.element_information1 ;
1064         l_tax_unit_id           := g_old_rec.tax_unit_id          ;
1065         l_full_name             := g_old_rec.full_name            ;
1066         l_business_group_id     := g_old_rec.business_group_id    ;
1067         l_old_effective_date    :=
1068                    TO_DATE(g_old_rec.effective_end_date, 'DD/MM/YYYY');
1069         l_first_time            := FALSE                          ;
1070 
1071         IF (p_person_id IS NULL) THEN
1072             IF (l_person_id IS NULL) THEN
1073                 IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
1074                     FND_FILE.PUT_LINE(FND_FILE.LOG,'No record found for Year = '
1075                         || TO_CHAR(p_year) ||' GRE =  ' || TO_CHAR(p_gre_id) ||
1076                      ' Business Group Id = ' || TO_CHAR(l_business_group_id));
1077                 ELSE
1078                     hr_utility.set_location('No record found for Year = ' ||
1079                         TO_CHAR(p_year) ||' GRE =  ' || TO_CHAR(p_gre_id) ||
1080                    ' Business Group Id = ' || TO_CHAR(l_business_group_id), 80);
1081                 END IF;
1082             END IF;
1083             EXIT WHEN C_All_Emp%NOTFOUND;
1084         ELSE
1085             IF (l_person_id IS NULL) THEN
1086                 IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
1087                     FND_FILE.PUT_LINE(FND_FILE.LOG, 'No record found for ' ||
1088                     'person Id = ' || TO_CHAR(p_person_id) || ' Year = ' ||
1089                     TO_CHAR(p_year) || ' Tax Unit Id = ' || TO_CHAR(p_gre_id) ||
1090                     ' Business Group Id = ' || TO_CHAR(l_business_group_id));
1091                 ELSE
1092                     hr_utility.set_location('No record found for person Id = ' ||
1093                     TO_CHAR(p_person_id) || ' Year = ' || TO_CHAR(p_year) ||
1094                     ' Tax Unit Id = ' || TO_CHAR(p_gre_id) || ' Business Group Id
1095                     = ' || TO_CHAR(l_business_group_id), 85);
1096                 END IF;
1097             END IF;
1098             EXIT WHEN C_All_Emp%NOTFOUND;
1099         END IF;
1100     EXCEPTION
1101 
1102     WHEN OTHERS THEN
1103         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
1104             FND_FILE.PUT_LINE(FND_FILE.LOG,substr(SQLERRM, 1, 255) || ' in ' ||
1105            l_proc || ' ' || TO_CHAR(SQLCODE) || ' in cursor for Person id = ' ||
1106            TO_CHAR(g_old_rec.person_id) || ' ' || g_old_rec.full_name);
1107         ELSE
1108             hr_utility.set_location(substr(SQLERRM, 1, 255) || ' in ' ||
1109            l_proc || ' ' || TO_CHAR(SQLCODE) || ' in cursor for Person id = ' ||
1110             TO_CHAR(g_old_rec.person_id) || ' ' || g_old_rec.full_name, 1000);
1111        END IF;
1112     END;
1113     END LOOP;
1114     hr_utility.set_location('Closing the cursor ', 100);
1115     Close C_All_Emp;
1116     hr_utility.set_location('Calling Business_rule_proc ', 150);
1117 
1118 -- The proc takes care of the case when p_person_id is null. Then it finds
1119 -- out all the persons.
1120 
1121     Business_rule_proc(p_year,
1122                        p_person_id,
1123                        p_gre_id);
1124     hr_utility.set_location(' Leaving:'||l_proc, 1500);
1125 EXCEPTION
1126     WHEN NO_DATA_FOUND THEN
1127         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
1128             FND_FILE.PUT_LINE(FND_FILE.LOG,'No records found ');
1129         ELSE
1130             hr_utility.set_location('No records found ', 95);
1131         END IF;
1132     WHEN OTHERS THEN
1133         IF (FND_GLOBAL.CONC_REQUEST_ID <> -1 ) THEN
1134             FND_FILE.PUT_LINE(FND_FILE.LOG,substr(SQLERRM, 1, 128) || ' in ' ||
1135 l_proc || ' ' || TO_CHAR(SQLCODE));
1136         ELSE
1137             hr_utility.set_location(substr(SQLERRM, 1, 128) || ' in ' ||
1138 l_proc || ' ' || TO_CHAR(SQLCODE), 100);
1139        END IF;
1140 END rollover_process;
1141 END pay_us_def_comp_457;