DBA Data[Home] [Help]

PACKAGE BODY: APPS.HR_GBBAL

Source


1 PACKAGE BODY hr_gbbal AS
2 /* $Header: pygbbal.pkb 120.14 2011/04/26 11:57:01 npannamp ship $ */
3 --------------------------------------------------------------------------------
4 g_assignment_action_id number;
5 g_start_of_year per_time_periods.regular_payment_date%type;
6 -- g_initialization_exists number;
7 g_asg_td_ytd number;
8 g_assignment_action_id2 number;
9 g_assignment_id number;
10 g_action_sequence number;
11 g_effective_date date;
12 g_ni_a_id number;
13 g_ni_b_id number;
14 g_ni_c_id number;
15 g_ni_d_id number;
16 g_ni_e_id number;
17 g_ni_f_id number;
18 g_ni_g_id number;
19 g_ni_j_id number;
20 g_ni_l_id number;
21 g_ni_s_id number;
22 g_ni_a_able_id number;
23 g_ni_b_able_id number;
24 g_ni_c_able_id number;
25 g_ni_d_able_id number;
26 g_ni_e_able_id number;
27 g_ni_f_able_id number;
28 g_ni_g_able_id number;
29 g_ni_j_able_id number;
30 g_ni_l_able_id number;
31 g_ni_s_able_id number;
32 g_ni_a_defbal_id number;
33 g_ni_b_defbal_id number;
34 g_ni_c_defbal_id number;
35 g_ni_d_defbal_id number;
36 g_ni_e_defbal_id number;
37 g_ni_f_defbal_id number;
38 g_ni_g_defbal_id number;
39 g_ni_j_defbal_id number;
40 g_ni_l_defbal_id number;
41 g_ni_s_defbal_id number;
42 g_ni_a_able_defbal_id number;
43 g_ni_b_able_defbal_id number;
44 g_ni_c_able_defbal_id number;
45 g_ni_d_able_defbal_id number;
46 g_ni_e_able_defbal_id number;
47 g_ni_f_able_defbal_id number;
48 g_ni_g_able_defbal_id number;
49 g_ni_j_able_defbal_id number;
50 g_ni_l_able_defbal_id number;
51 g_ni_s_able_defbal_id number;
52 g_ni_a_exists number;
53 g_ni_b_exists number;
54 g_ni_c_exists number;
55 g_ni_d_exists number;
56 g_ni_e_exists number;
57 g_ni_f_exists number;
58 g_ni_g_exists number;
59 g_ni_j_exists number;
60 g_ni_l_exists number;
61 g_ni_s_exists number;
62 g_ni_cat_indicator_table_id number;
63 g_ni_element_type_id number;
64 g_ni_a_element_type_id number;
65 g_ni_b_element_type_id number;
66 g_ni_c_element_type_id number;
67 g_ni_d_element_type_id number;
68 g_ni_e_element_type_id number;
69 g_ni_f_element_type_id number;
70 g_ni_g_element_type_id number;
71 g_ni_j_element_type_id number;
72 g_ni_l_element_type_id number;
73 g_ni_s_element_type_id number;
74 g_action_typer pay_payroll_actions.action_type%TYPE;
75 g_action_typeq pay_payroll_actions.action_type%TYPE;
76 g_action_typeb pay_payroll_actions.action_type%TYPE;
77 g_balance number;
78 
79 -- return the start of the span (year/quarter/week)
80 FUNCTION span_start(
81   p_input_date    DATE,
82   p_frequency   NUMBER DEFAULT 1,
83   p_start_dd_mm   VARCHAR2 DEFAULT '06-04-')
84 RETURN DATE
85 IS
86   l_year  NUMBER(4);
87   l_start DATE;
88   l_start_dd_mm varchar2(6);
89   l_correct_format BOOLEAN;
90 --
91 BEGIN
92   l_year := FND_NUMBER.CANONICAL_TO_NUMBER(TO_CHAR(p_input_date,'YYYY'));
93    --
94    -- Check that the passed in start of year
95    -- is in the correct format. Add a hyphen if one is missing
96    -- from the end, and ensure DD-MM- only has 6 characters.
97    -- If none of these 2 criteria are met, return null.
98    --
99    if length(p_start_dd_mm) = 5 and instr(p_start_dd_mm,'-',-1) = 3 then
100       l_start_dd_mm := p_start_dd_mm||'-';
101       l_correct_format := TRUE;
102    elsif length(p_start_dd_mm) = 6 and instr(p_start_dd_mm,'-',-1) = 6 then
103       l_start_dd_mm := p_start_dd_mm;
104       l_correct_format := TRUE;
105    else
106       l_correct_format := FALSE;
107    end if;
108    --
109    if l_correct_format then
110       IF p_input_date >= TO_DATE(l_start_dd_mm||TO_CHAR(l_year),'DD-MM-YYYY') THEN
111         l_start := TO_DATE(l_start_dd_mm||TO_CHAR(l_year),'DD-MM-YYYY');
112       ELSE
113         l_start := TO_DATE(l_start_dd_mm||TO_CHAR(l_year -1),'DD-MM-YYYY');
114       END IF;
115       -- cater for weekly based frequency based on 52 per annum
116       IF p_frequency IN (52,26,13) THEN
117         l_start := p_input_date - MOD(p_input_date - l_start, 7 * (52/p_frequency));
118       ELSE
119       -- cater for monthly based frequency based on 12 per annum
120         l_start := ADD_MONTHS(l_start, (12/p_frequency) * TRUNC(MONTHS_BETWEEN(
121       p_input_date,l_start)/(12/p_frequency)));
122       END IF;
123    end if;
124 --
125 RETURN l_start;
126 END span_start;
127 -------------------------------------------------------------------------------
128 --
129 -- Function SPAN_END. This returns the end of the person level
130 -- (statutory) period.
131 --
132 -------------------------------------------------------------------------------
133 -- return the end of the span (year/quarter/week)
134 FUNCTION span_end(
135         p_input_date            DATE,
136         p_frequency             NUMBER DEFAULT 1,
137         p_start_dd_mm           VARCHAR2 DEFAULT '06-04-')
138 RETURN DATE
139 IS
140         l_year  NUMBER(4);
141         l_end DATE;
142         l_start_dd_mm varchar2(6);
143         l_correct_format BOOLEAN;
144 --
145 BEGIN
146         l_year := FND_NUMBER.CANONICAL_TO_NUMBER(TO_CHAR(p_input_date,'YYYY'));
147    --
148    -- Check that the passed in start of year
149    -- is in the correct format. Add a hyphen if one is missing
150    -- from the end, and ensure DD-MM- only has 6 characters.
151    -- If none of these 2 criteria are met, return null.
152    --
153    if length(p_start_dd_mm) = 5 and instr(p_start_dd_mm,'-',-1) = 3 then
154       l_start_dd_mm := p_start_dd_mm||'-';
155       l_correct_format := TRUE;
156    elsif length(p_start_dd_mm) = 6 and instr(p_start_dd_mm,'-',-1) = 6 then
157       l_start_dd_mm := p_start_dd_mm;
158       l_correct_format := TRUE;
159    else
160       l_correct_format := FALSE;
161    end if;
162    --
163    if l_correct_format then
164       IF p_input_date >= TO_DATE(l_start_dd_mm||TO_CHAR(l_year),'DD-MM-YYYY') THEN
165         l_end := TO_DATE(l_start_dd_mm||TO_CHAR(l_year),'DD-MM-YYYY');
166       ELSE
167         l_end := TO_DATE(l_start_dd_mm||TO_CHAR(l_year -1),'DD-MM-YYYY');
168       END IF;
169       -- cater for weekly based frequency based on 52 per annum
170       IF p_frequency IN (52,26,13) THEN
171         l_end := p_input_date - MOD(p_input_date - l_end, 7 * (52/p_frequency))                 + ((7 * 52/p_frequency)-1);
172       ELSE
173       -- cater for monthly based frequency based on 12 per annum
174         l_end := (add_months (ADD_MONTHS(l_end, (12/p_frequency)
175     * TRUNC(MONTHS_BETWEEN(p_input_date,l_end)/(12/p_frequency))),
176           12/p_frequency) -1);
177       END IF;
178    end if;
179 --
180 RETURN l_end;
181 END span_end;
182 --
183 --------------------------------------------------------------------------------
184 --
185 --                      GET CORRECT TYPE (private)
186 --
187 --
188 --------------------------------------------------------------------------------
189 --
190 -- This is a validation check to ensure that the assignment action is of the
191 -- correct type. This is called from all assignment action mode functions.
192 -- The assignment id is returned (and not assignment action id) because
193 -- this is to be used in the expired latest balance check. This function thus
194 -- has two uses - to validate the assignment action, and give the corresponding
195 -- assignmment id for that action.
196 --
197 FUNCTION get_correct_type(p_assignment_action_id IN NUMBER)
198 --
199 RETURN NUMBER IS
200 --
201    l_assignment_id  NUMBER;
202 --
203     cursor get_corr_type (c_assignment_action_id IN NUMBER) is
204     SELECT assignment_id
205     FROM pay_assignment_actions paa,
206          pay_payroll_actions    ppa
207     WHERE
208          paa.assignment_action_id = c_assignment_action_id
209     AND  ppa.payroll_action_id = paa.payroll_action_id
210     AND  ppa.action_type        in ('R', 'Q', 'I', 'V', 'B');
211 --
212 BEGIN
213 --
214    open get_corr_type(p_assignment_action_id);
215    fetch get_corr_type into l_assignment_id;
216    close get_corr_type;
217 --
218 RETURN l_assignment_id;
219 --
220 END get_correct_type;
221 --------------------------------------------------------------------------------
222 --
223 --                      GET LATEST ACTION ID (private)
224 --
225 --
226 --------------------------------------------------------------------------------
227 -- This function returns the latest assignment action ID given an assignment
228 -- and effective date. This is called from all Date Mode functions.
229 --
230 FUNCTION get_latest_action_id (p_assignment_id IN NUMBER,
231              p_effective_date IN DATE)
232 RETURN NUMBER IS
233 --
234    l_assignment_action_id   NUMBER;
235    l_master_asg_action_id       NUMBER;
236    l_child_asg_action_id       NUMBER;
237 --
238 
239 /* bug fix 4493616 start*/
240 cursor get_master_latest_id (c_assignment_id IN NUMBER,
241                  c_effective_date IN DATE) is
242     SELECT /*+ USE_NL(paa, ppa) */
243          fnd_number.canonical_to_number(substr(max(lpad(paa.action_sequence,15,'0')||
244          paa.assignment_action_id),16))
245     FROM pay_assignment_actions paa,
246          pay_payroll_actions    ppa
247     WHERE
248          paa.assignment_id = c_assignment_id
249     AND  ppa.payroll_action_id = paa.payroll_action_id
250     AND  paa.source_action_id is null
251     AND  ppa.effective_date  <= c_effective_date
252     AND  ppa.action_type     in ('R', 'Q', 'I', 'V', 'B');
253  -- AND  paa.action_status   = 'C';
254 --
255 
256 cursor get_latest_id (c_assignment_id IN NUMBER,
257           c_effective_date IN DATE,
258           c_master_asg_action_id IN NUMBER) is
259     SELECT /*+ USE_NL(paa, ppa) */
260          fnd_number.canonical_to_number(substr(max(lpad(paa.action_sequence,15,'0')||
261          paa.assignment_action_id),16))
262     FROM pay_assignment_actions paa,
263          pay_payroll_actions    ppa
264     WHERE
265          paa.assignment_id = c_assignment_id
266     AND  ppa.payroll_action_id = paa.payroll_action_id
267     AND  paa.source_action_id is not null
268     AND  ppa.effective_date <= c_effective_date
269     AND  ppa.action_type        in ('R', 'Q')
270   --AND  paa.action_status = 'C'
271     AND  paa.source_action_id = c_master_asg_action_id ;
272 --
273 BEGIN
274 --
275 
276     open  get_master_latest_id(p_assignment_id, p_effective_date);
277     fetch get_master_latest_id into l_master_asg_action_id;
278 
279     if   get_master_latest_id%found then
280 
281    open  get_latest_id(p_assignment_id, p_effective_date,l_master_asg_action_id);
282    fetch get_latest_id into l_child_asg_action_id;
283 
284    if l_child_asg_action_id is not null then
285       l_assignment_action_id := l_child_asg_action_id;
286    else
287       l_assignment_action_id := l_master_asg_action_id;
288    end if;
289    close get_latest_id;
290     end if;
291     close get_master_latest_id;
292 /* bug fix 4493616 end*/
293 --
294 RETURN l_assignment_action_id;
295 --
296 END get_latest_action_id;
297 --
298 --------------------------------------------------------------------------------
299 --
300 --                       DIMENSION RELEVANT  (private)
301 --
302 --
303 --------------------------------------------------------------------------------
304 --
305 -- This function checks that a value is required for the dimension
306 -- for this particular balance type. If so, the defined balance is returned.
307 --
308 FUNCTION dimension_relevant(p_balance_type_id      IN NUMBER,
309           p_database_item_suffix IN VARCHAR2)
310 RETURN NUMBER IS
311 --
312    l_defined_balance_id NUMBER;
313 --
314    cursor relevant(c_balance_type_id IN NUMBER,
315        c_db_item_suffix  IN VARCHAR2) IS
316    select pdb.defined_balance_id from
317     pay_defined_balances pdb,
318     pay_balance_dimensions pbd
319    where pdb.balance_dimension_id = pbd.balance_dimension_id
320    and pbd.database_item_suffix =  c_db_item_suffix
321    and pdb.balance_type_id = c_balance_type_id;
322 --
323 BEGIN
324 --
325    open relevant(p_balance_type_id, p_database_item_suffix);
326    fetch relevant into l_defined_balance_id;
327    close relevant;
328 --
329 RETURN l_defined_balance_id;
330 --
331 END dimension_relevant;
332 --------------------------------------------------------------------------------
333 --
334 --      GET LATEST DATE (private)
335 --
336 --
337 --------------------------------------------------------------------------------
338 --
339 -- Find out the effective date of the latest balance of a particular
340 -- assignment action.
341 --
342 FUNCTION get_latest_date(
343         p_assignment_action_id  NUMBER)
344 RETURN DATE IS
345 --
346    l_effective_date date;
347 --
348    cursor c_bal_date is
349    SELECT    ppa.effective_date
350    FROM      pay_payroll_actions ppa,
351              pay_assignment_actions paa
352    WHERE     paa.payroll_action_id = ppa.payroll_action_id
353    AND       paa.assignment_action_id = p_assignment_action_id;
354 --
355  begin
356 --
357    OPEN  c_bal_date;
358    FETCH c_bal_date into l_effective_date;
359    if c_bal_date%NOTFOUND then
360       l_effective_date := null;
361 --       raise_application_error(-20000,'This assignment action is invalid');
362    end if;
363    CLOSE c_bal_date;
364 --
365    RETURN l_effective_date;
366 END get_latest_date;
367 --
368 -------------------------------------------------------------------------------
369 --
370 --      GET_EXPIRED_YEAR_DATE (private)
371 --
372 -------------------------------------------------------------------------------
373 --
374 -- Find out the expiry of the year of the assignment action's effective date,
375 -- for expiry checking in the main functions.
376 --
377 FUNCTION get_expired_year_date(
378              p_action_effective_date DATE)
379 RETURN DATE IS
380 --
381    l_expired_date DATE;
382    l_year_add_no  NUMBER;
383 --
384 BEGIN
385 --
386  if p_action_effective_date is not null then
387 --
388    if  p_action_effective_date <
389                   to_date('06-04-' || to_char(p_action_effective_date,'YYYY'),
390                  'DD-MM-YYYY')  then
391         l_year_add_no := 0;
392    else l_year_add_no := 1;
393    end if;
394 --
395 -- Set expired date to the 6th of April next.
396 --
397    l_expired_date :=
398      ( to_date('06-04-' || to_char( fnd_number.canonical_to_number(to_char(
399      p_action_effective_date,'YYYY')) + l_year_add_no),'DD-MM-YYYY'));
400 --
401  end if;
402 --
403    RETURN l_expired_date;
404 --
405 END get_expired_year_date;
406 --
407 ------------------------------------------------------------------------------
408 --
409 --      GET_EXPIRED_TWO_YEAR_DATE (private)
410 -------------------------------------------------------------------------------
411 --
412 -- Find out the expiry of the year of the assignment action's effective date,
413 -- for the ASG_TD_ODD_TWO_YTD and ASG_TD_EVEN_TWO_YTD
414 --
415 FUNCTION get_expired_two_year_date(
416              p_action_effective_date DATE,
417              p_odd_even              VARCHAR2 )
418 RETURN DATE IS
419    --
420    l_expired_date DATE;
421    l_year_add_no  NUMBER;
422    --
423 BEGIN
424    --
425    IF p_action_effective_date is not null THEN
426       --
427       IF p_action_effective_date < to_date('06-04-' ||
428             to_char(p_action_effective_date,'YYYY'),'DD-MM-YYYY')  THEN
429          l_year_add_no := 0;
430       ELSE
431          l_year_add_no := 1;
432       END IF;
433       --
434       -- add a year depending on the odd or even dimension
435       --
436       IF p_odd_even = 'EVEN' THEN
437          IF mod(to_number(to_char(p_action_effective_date,'yyyy')),2) = 1 THEN
438            l_year_add_no := l_year_add_no + 1;
439          ELSE
440            l_year_add_no := l_year_add_no;
441          END IF;
442       ELSIF p_odd_even = 'ODD' then
443         IF mod(to_number(to_char(p_action_effective_date,'yyyy')),2) = 1 THEN
444            l_year_add_no := l_year_add_no;
445          ELSE
446            l_year_add_no := l_year_add_no + 1;
447          END IF;
448       END IF;
449       --
450       -- Set expired date to the 6th of April of the expiring year.
451       --
452       l_expired_date :=  ( to_date('06-04-' ||
453            to_char( fnd_number.canonical_to_number(to_char(
454            p_action_effective_date,'YYYY')) + l_year_add_no),'DD-MM-YYYY'));
455       --
456    END IF;
457    --
458    RETURN l_expired_date;
459    --
460 END get_expired_two_year_date;
461 ---------------------------------------------------------------------------
462 --
463 -- what is the latest reset date for a particular dimension
464 FUNCTION dimension_reset_date(
465   p_dimension_name  VARCHAR2,
466   p_user_date     DATE,
467   p_business_group_id NUMBER)
468 RETURN DATE
469 IS
470   l_start_dd_mon    VARCHAR2(7);
471   l_global_name   VARCHAR2(30);
472   l_period_from_date  DATE;
473   l_frequency   NUMBER;
474   l_start_reset   NUMBER;
475 BEGIN
476   IF SUBSTR(p_dimension_name,31,8) = 'USER-REG' THEN -- [
477     l_start_reset := INSTR(p_dimension_name,'RESET',30);
478     l_start_dd_mon := SUBSTR(p_dimension_name, l_start_reset - 6, 5);
479     l_frequency := FND_NUMBER.CANONICAL_TO_NUMBER(SUBSTR
480                                      (p_dimension_name, l_start_reset + 6, 2));
481     l_period_from_date := span_start(p_user_date,
482                                       l_frequency, l_start_dd_mon);
483   END IF; -- ]
484 
485   /*                                                */
486   /* User Irregular Balance are not yet implemented */
487   /*                                                */
488   /*
489   IF SUBSTR(p_dimension_name,1,14) = 'USER IRREGULAR' THEN -- [
490   --      find the global set up with the reset dates
491   --      need to code exception if there isn't a valid one (default to calendar
492   --      also make this code a local function
493     l_start_word := INSTR(p_dimension_name,'BASED ON') + 8;
494     l_global_name := SUBSTR(p_dimension_name, l_start_word);
495     SELECT
496       effective_start_date
497     INTO
498       l_period_from_date
499     FROM
500       ff_globals_f
501     WHERE   global_name = l_global_name
502     AND business_group_id = p_business_group_id
503     AND p_user_date BETWEEN effective_start_date AND effective_end_date;
504   END IF; -- ]
505   */
506 
507   RETURN l_period_from_date;
508 END dimension_reset_date;
509 --------------------------------------------------------------------------------
510 -- when did the director become a director
511 -- find the earliest person row that was date effcetive in this year with
512 -- director flag set
513 FUNCTION start_director(
514         p_assignment_id         NUMBER,
515         p_start_date            DATE  ,
516         p_end_date              DATE )
517 RETURN DATE
518 IS
519         l_event_from_date date;
520 BEGIN
521         select nvl(min(P.effective_start_date)
522                   ,fnd_date.canonical_to_date('4712/12/31'))
523                 into l_event_from_date
524                    from per_people_f p,  /* should this be all ? */
525                         per_assignments_f ass
526                    where p.per_information2 = 'Y'
527                    and ASS.person_id = P.person_id
528                    and P.effective_start_date <= p_end_date
529                    and p.effective_end_date >=   p_start_date
530                    and p_end_date between
531                                 ass.effective_start_date and ass.effective_end_date
532                    and ass.assignment_id = p_assignment_id ;
533 
534         RETURN l_event_from_date;
535 END start_director;
536 --------------------------------------------------------------------------------
537 -- Function:    per_datemode_balance
538 -- Description: Introduced for bug fix 3436701, this expires Person level
539 -- balances before calling the core balance UE process to get the value.
540 -- The Core BUE cannot be called in datemode directly as this causes an
541 -- error from the view, because it issues DML and commits.
542 --------------------------------------------------------------------------------
543 Function per_datemode_balance(p_assignment_action_id in number,
544                               p_defined_balance_id   in number,
545                               p_database_item_suffix in varchar2,
546                               p_effective_date       in date) return number is
547 --
548     cursor expired_time_period (c_assignment_action_id IN NUMBER) is
549     SELECT ptp.end_date, ppa.effective_date
550     FROM per_time_periods ptp,
551          pay_payroll_actions ppa,
552          pay_assignment_actions paa
553     WHERE
554          paa.assignment_action_id = c_assignment_action_id
555     AND  paa.payroll_action_id = ppa.payroll_action_id
556     AND  ppa.time_period_id = ptp.time_period_id;
557 --
558     l_period_end_date       DATE;
559     l_date_paid             DATE;
560     l_balance               NUMBER;
561     l_action_eff_date       DATE;
562     l_expiry_date           DATE;
563 --
564 BEGIN
565 --
566   IF p_database_item_suffix in ('_PER_TD_STAT_PTD',
567                                 '_PER_TD_PTD',
568                                 '_PER_NI_PTD',
569                                 '_PER_TD_CPE_STAT_PTD') THEN
570      open expired_time_period(p_assignment_action_id);
571      fetch expired_time_period INTO l_period_end_date, l_date_paid;
572      close expired_time_period;
573      --hr_utility.trace('PER - Dates: end='||l_period_end_date||' paid='|| l_date_paid);
574      --
575      l_expiry_date := greatest(l_period_end_date,l_date_paid);
576      --
577   ELSIF p_database_item_suffix in ('_PER_TD_YTD',
578                                    '_PER_TD_DIR_YTD',
579                                    '_PER_TD_CPE_YTD') THEN
580      l_action_eff_date := get_latest_date(p_assignment_action_id);
581      --
582      l_expiry_date := get_expired_year_date(l_action_eff_date);
583   ELSIF p_database_item_suffix = '_PER_TD_EVEN_TWO_YTD' THEN
584      --
585      l_action_eff_date := get_latest_date(p_assignment_action_id);
586      l_expiry_date := get_expired_two_year_date(l_action_eff_date,'EVEN');
587   ELSIF p_database_item_suffix = '_PER_TD_ODD_TWO_YTD' THEN
588      --
589      l_action_eff_date := get_latest_date(p_assignment_action_id);
590      l_expiry_date := get_expired_two_year_date(l_action_eff_date,'ODD');
591   ELSE
592      -- A non-covered PER expiry, call pkg without expiring here
593      l_expiry_date := to_date('31/12/4712','DD/MM/YYYY');
594   END IF;
595   --
596   -- Expiry dates set, check the effective date
597   --
598   /*Bug fix 5104943*/
599  IF p_database_item_suffix in ('_PER_TD_STAT_PTD', '_PER_TD_PTD','_PER_NI_PTD','_PER_TD_CPE_STAT_PTD') THEN
600     if  p_effective_date > l_expiry_date then
601         -- Balance has expired
602         l_balance := 0;
603     else
604         l_balance := pay_balance_pkg.get_value(p_defined_balance_id,
605                  p_assignment_action_id);
606     end if;
607  ELSE
608           if  p_effective_date >= l_expiry_date then
609         -- Balance has expired
610         l_balance := 0;
611     else
612         l_balance := pay_balance_pkg.get_value(p_defined_balance_id,
613                  p_assignment_action_id);
614     end if;
615  END IF;
616 
617 --
618 RETURN l_balance;
619 --
620 END per_datemode_balance;
621 --------------------------------------------------------------------------------
622 --
623 --                               BALANCE                                   --
624 --  Called from calc_all_balances for User Regulars and other non UK seeded
625 --  balances, also called from pay_gb_balances_v.
626 --
627 --------------------------------------------------------------------------------
628 --
629 FUNCTION balance(
630         p_assignment_action_id  IN NUMBER,
631         p_defined_balance_id    IN NUMBER,
632         p_effective_date        IN DATE DEFAULT NULL)
633 RETURN NUMBER
634 IS
635 --
636         l_balance               NUMBER;
637         l_balance1              NUMBER;
638         l_assignment_id         NUMBER;
639         l_balance_type_id       NUMBER;
640         l_period_from_date      DATE := FND_DATE.CANONICAL_TO_DATE('0001/01/01');
641         l_event_from_date       DATE := FND_DATE.CANONICAL_TO_DATE('0001/01/01');
642         l_to_date               DATE;
643         l_regular_payment_date  DATE;
644         l_action_sequence       NUMBER;
645         l_business_group_id     NUMBER;
646         l_dimension_bgid        NUMBER;
647         l_dimension_name        pay_balance_dimensions.dimension_name%TYPE;
648         l_database_item_suffix  pay_balance_dimensions.database_item_suffix%TYPE;
649         l_legislation_code      pay_balance_dimensions.legislation_code%TYPE;
650         l_latest_value_exists   VARCHAR(2);
651         l_period_end_date       DATE;
652         l_date_paid             DATE;
653 --
654         cursor c1  (c_asg_action_id IN NUMBER,
655                     c_defined_balance_id IN NUMBER)is
656         SELECT value, assignment_id
657         from  pay_assignment_latest_balances
658         Where assignment_action_id = c_asg_action_id
659         and   defined_balance_id = c_defined_balance_id;
660 --
661         cursor action_context is
662         SELECT
663                 BAL_ASSACT.assignment_id,
664                 BAL_ASSACT.action_sequence,
665                 BACT.effective_date,
666                 PTP.regular_payment_date,
667                 BACT.business_group_id
668         FROM
669                 pay_assignment_actions  BAL_ASSACT,
670                 pay_payroll_actions             BACT,
671                 per_time_periods                        PTP
672         WHERE
673                 BAL_ASSACT.assignment_action_id = p_assignment_action_id
674         AND     PTP.time_period_id = BACT.time_period_id
675         AND     BACT.payroll_action_id = BAL_ASSACT.payroll_action_id;
676 --
677         cursor balance_dimension is
678         SELECT
679                 DB.balance_type_id,
680                 DIM.dimension_name,
681                 DIM.database_item_suffix ,
682                 DIM.legislation_code,
683                 DIM.business_group_id
684         FROM
685                 pay_defined_balances    DB,
686                 pay_balance_dimensions  DIM
687         WHERE   DB.defined_balance_id = p_defined_balance_id
688         AND     DIM.balance_dimension_id = DB.balance_dimension_id;
689 --
690 BEGIN
691 --
692 -- get the context of the using action
693 --
694    open action_context;
695    FETCH action_context INTO
696          l_assignment_id,
697          l_action_sequence,
698          l_to_date,
699          l_regular_payment_date,
700          l_business_group_id;
701    CLOSE action_context;
702 --
703 -- from the item name determine what balance and dimension it is
704 --
705    open balance_dimension;
706    FETCH balance_dimension INTO
707          l_balance_type_id,
708          l_dimension_name,
709          l_database_item_suffix ,
710          l_legislation_code,
711          l_dimension_bgid;
712    close balance_dimension;
713 --
714 -- Bug 2755875. New routes added that are core routes. In this case
715 -- the core BUE must be called with the passed-in parameters.
716 -- This will use the latest balance if it exists.
717 -- Check the BGID incase this is a user-defined user-reg dimension.
718 -- Bug 2886012, handle the exception just incase no dimension found.
719 
720    IF l_legislation_code is null AND l_dimension_bgid is null then
721    --
722      BEGIN
723         l_balance := pay_balance_pkg.get_value(
724                     p_assignment_action_id => p_assignment_action_id,
725                     p_defined_balance_id   => p_defined_balance_id);
726      EXCEPTION WHEN NO_DATA_FOUND THEN
727         l_balance := null;
728      END;
729    --
730    ELSE -- A GB or user balance
731 
732    -- Does the assignment action id exist in the latest balances table
733    --
734     /* Commented for bug fix 4452262*/
735     /*  OPEN c1 (p_assignment_action_id, p_defined_balance_id);
736       FETCH c1 INTO l_balance, l_assignment_id;
737          IF c1%FOUND THEN l_latest_value_exists := 'T';
738          ELSE l_latest_value_exists := 'F';
739          END IF;
740       CLOSE c1;
741       */
742 
743       /*For bug fix 4452262*/
744       l_latest_value_exists := 'F';
745       for i in c1 (p_assignment_action_id, p_defined_balance_id)
746       loop
747             l_balance       :=  nvl(l_balance,0) + nvl(i.value,0);
748       l_assignment_id := i.assignment_id;
749 
750       l_latest_value_exists := 'T';
751 
752       end loop;
753    --
754    -- Bug 923689. Raise NDF to stop date-format error from span_start.
755    --
756       IF l_to_date is null
757          then RAISE NO_DATA_FOUND;
758       end if;
759    --
760    -- If the latest bal value doesn't exist further action is necessary
761    --
762       IF l_latest_value_exists = 'F' then
763    --
764    --   for seeded person level dimensions call the core function
765    --
766         IF substr(l_database_item_suffix,1,4) = '_PER'
767                 and l_legislation_code = 'GB' THEN
768           BEGIN
769             -- Bug fix 3436701.
770             IF p_effective_date is not null then
771               -- This is a Datemode call for PER level balance
772               l_balance1 := per_datemode_balance(p_assignment_action_id,
773                                                 p_defined_balance_id,
774                                                 l_database_item_suffix,
775                                                 p_effective_date);
776 
777               /*For bug fix 4452262*/
778        g_balance := nvl(g_balance,0) + nvl(l_balance1,0);
779              l_balance := g_balance;
780 
781 
782             ELSE
783              -- Assignment Action mode call as before
784               l_balance := pay_balance_pkg.get_value(p_defined_balance_id,
785                                                  p_assignment_action_id);
786 
787 
788             END IF;
789            EXCEPTION WHEN NO_DATA_FOUND THEN
790             l_balance := null;
791           END;
792    --
793         ELSE  -- Not a person-level balance, either USER-REG OR CALENDAR
794    --
795    --      IMPORTANT NOTE: For user-regs this must never call core
796    --      balance package, must work out route locally.
797    --
798    --      from the dimension work out the from dates
799    --      CALENDAR has no event start
800    --
801            IF l_dimension_name = '_ASG_CALENDAR_YTD' THEN
802               l_period_from_date := TRUNC(l_regular_payment_date,'YYYY');
803            END IF;
804            IF l_dimension_name = '_ASG_CALENDAR_QTD' THEN
805               l_period_from_date := TRUNC(l_regular_payment_date,'Q');
806            END IF;
807    --
808    --      evaluate user-defined (USER-REG) dimensions
809    --
810            IF SUBSTR(l_dimension_name,31,4) = 'USER' THEN
811               l_period_from_date := dimension_reset_date(
812                                                 l_dimension_name,
813                                                 l_regular_payment_date,
814                                                 l_business_group_id);
815            END IF;
816    --
817    --      USER REGS MUST USE THIS GENERIC ROUTE FUNCTION.
818    --
819            l_balance := calc_balance(
820                 l_assignment_id,
821                 l_balance_type_id,
822                 l_period_from_date,
823                 l_event_from_date,
824                 l_to_date,
825                 l_action_sequence);
826         END IF; -- Person Level Balance
827      END IF; -- Latest Balance
828    END IF; -- Core Balance
829 --
830    RETURN l_balance;
831 --
832 END balance;
833 --
834 --------------------------------------------------------------------------------
835 --
836 --                          GET_LATEST_ELEMENT_BAL (Private)
837 --    calculate latest balances for element dimensions
838 --
839 --------------------------------------------------------------------------------
840 --
841 FUNCTION get_latest_element_bal(
842         p_assignment_action_id  IN NUMBER,
843         p_defined_bal_id        IN NUMBER,
844         p_source_id           IN NUMBER)
845 --
846 RETURN NUMBER IS
847 --
848    l_balance               NUMBER;
849    l_db_item_suffix        VARCHAR2(30);
850    l_defined_bal_id      NUMBER;
851 --
852    cursor element_latest_bal(c_assignment_action_id IN NUMBER,
853            c_defined_bal_id     IN NUMBER,
854            c_source_id            IN NUMBER) is
855    select palb.value
856    from pay_assignment_latest_balances palb,
857         pay_balance_context_values pbcv
858    where pbcv.context_id = c_source_id
859    and   pbcv.latest_balance_id = palb.latest_balance_id
860    and   palb.assignment_action_id = c_assignment_action_id
861    and   palb.defined_balance_id = c_defined_bal_id;
862 --
863 BEGIN
864 --
865    open element_latest_bal(p_assignment_action_id,
866          p_defined_bal_id,
867          p_source_id);
868    fetch element_latest_bal into l_balance;
869    close element_latest_bal;
870 --
871 RETURN l_balance;
872 --
873 END get_latest_element_bal;
874 
875 --
876 -----------------------------------------------------------------------------
877 --
878 --      CALC_ELEMENT_CO_REF_ITD_BAL
879 -----------------------------------------------------------------------------
880 --
881 /* For bug fix 4452262*/
882 FUNCTION calc_element_co_itd_bal(p_assignment_action_id IN NUMBER,
883                    p_balance_type_id      IN NUMBER,
884                p_source_id          IN NUMBER,
885                p_source_text          IN VARCHAR2)
886 RETURN NUMBER IS
887 --
888    l_balance      NUMBER;
889    l_defined_bal_id NUMBER;
890    l_context NUMBER;
891 --
892 
893 cursor get_context_id is
894 SELECT CONTEXT_ID
895 FROM FF_CONTEXTS
896 where context_name ='SOURCE_TEXT';
897 
898 BEGIN
899 --
900    l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ELEMENT_CO_REF_ITD');
901 
902    open get_context_id;
903    fetch get_context_id into l_context;
904    close get_context_id;
905 
906    if l_defined_bal_id is not null then
907 
908       l_balance := get_latest_element_bal(p_assignment_action_id,
909                   l_defined_bal_id,
910                   p_source_id);
911       if l_balance is null then
912            pay_balance_pkg.set_context('ORIGINAL_ENTRY_ID'
913                                     , p_source_id);
914      pay_balance_pkg.set_context('SOURCE_TEXT'
915                                     , p_source_text);
916 
917           l_balance := pay_balance_pkg.get_value(l_defined_bal_id, p_assignment_action_id);
918      end if;
919    else l_balance := null;
920 --
921    end if;
922 --
923 RETURN l_balance;
924 --
925 END calc_element_co_itd_bal;
926 -----------------------------------------------------------------------------
927 --
928 --      CALC_ELEMENT_ITD_BAL
929 -----------------------------------------------------------------------------
930 --
931 FUNCTION calc_element_itd_bal(p_assignment_action_id IN NUMBER,
932                 p_balance_type_id      IN NUMBER,
933             p_source_id      IN NUMBER)
934 RETURN NUMBER IS
935 --
936    l_balance      NUMBER;
937    l_defined_bal_id NUMBER;
938 --
939 BEGIN
940 --
941    l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ELEMENT_ITD');
942    if l_defined_bal_id is not null then
943       l_balance := get_latest_element_bal(p_assignment_action_id,
944                   l_defined_bal_id,
945                   p_source_id);
946       if l_balance is null then
947          pay_balance_pkg.set_context('ORIGINAL_ENTRY_ID'
948                                     , p_source_id);
949          l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
950                                             p_assignment_action_id);
951 --
952       end if;
953    else l_balance := null;
954 --
955    end if;
956 --
957 RETURN l_balance;
958 --
959 END calc_element_itd_bal;
960 --
961 -----------------------------------------------------------------------------
962 --
963 --                      CALC_ELEMENT_PTD_BAL
964 -----------------------------------------------------------------------------
965 --
966 FUNCTION calc_element_ptd_bal(p_assignment_action_id IN NUMBER,
967                               p_balance_type_id      IN NUMBER,
968                               p_source_id            IN NUMBER)
969 RETURN NUMBER IS
970 --
971    l_balance        NUMBER;
972    l_defined_bal_id NUMBER;
973 --
974 BEGIN
975 --
976    l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ELEMENT_PTD');
977    if l_defined_bal_id is not null then
978 
979       l_balance := get_latest_element_bal(p_assignment_action_id,
980                                           l_defined_bal_id,
981                                           p_source_id);
982       if l_balance is null then
983 --
984          pay_balance_pkg.set_context('ORIGINAL_ENTRY_ID'
985                                     , p_source_id);
986          l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
987                                             p_assignment_action_id);
988       end if;
989    else l_balance := null;
990 --
991    end if;
992 --
993 RETURN l_balance;
994 --
995 END calc_element_ptd_bal;
996 --
997 -----------------------------------------------------------------------------
998 --
999 --                          CALC_ALL_BALANCES
1000 --    This is the generic overloaded function for calculating all balances
1001 --    in assignment action mode. NB Element level balances cannot be called
1002 --    from here as they require further context.
1003 -----------------------------------------------------------------------------
1004 --
1005 FUNCTION calc_all_balances(
1006          p_assignment_action_id IN NUMBER,
1007          p_defined_balance_id   IN NUMBER)
1008 --
1009 RETURN NUMBER
1010 IS
1011 --
1012     l_balance                   NUMBER;
1013     l_balance_type_id           NUMBER;
1014     l_dimension_name          VARCHAR2(80);
1015 --
1016     cursor get_balance_type_id(c_defined_balance_id IN NUMBER) IS
1017       select pdb.balance_type_id,
1018              pbd.dimension_name
1019       from   pay_balance_dimensions pbd,
1020              pay_defined_balances   pdb
1021       where  pdb.defined_balance_id = c_defined_balance_id
1022       and    pdb.balance_dimension_id = pbd.balance_dimension_id;
1023 --
1024 BEGIN
1025 --
1026    open get_balance_type_id(p_defined_balance_id);
1027    FETCH get_balance_type_id INTO
1028          l_balance_type_id, l_dimension_name;
1029    CLOSE get_balance_type_id;
1030 --
1031       If l_dimension_name like '%_ASG_YTD' then
1032          l_balance := calc_asg_ytd_action(p_assignment_action_id,
1033                                           l_balance_type_id);
1034       Elsif l_dimension_name  like '%_ASG_PROC_YTD' then
1035          l_balance := calc_asg_proc_ytd_action(p_assignment_action_id,
1036                                                l_balance_type_id);
1037       Elsif l_dimension_name like '%_ASG_RUN' then
1038          l_balance := calc_asg_run_action(p_assignment_action_id,
1039                                                l_balance_type_id);
1040       Elsif l_dimension_name like  '%_ASG_TD_YTD' then
1041          l_balance := calc_asg_td_ytd_action(p_assignment_action_id,
1042                                                l_balance_type_id);
1043       Elsif l_dimension_name like  '%_ASG_ITD' then
1044          l_balance := calc_asg_itd_action(p_assignment_action_id,
1045                                                l_balance_type_id);
1046       Elsif l_dimension_name like '%_ASG_QTD' then
1047          l_balance := calc_asg_qtd_action(p_assignment_action_id,
1048                                                l_balance_type_id);
1049       Elsif l_dimension_name like '%_ASG_STAT_YTD' then
1050          l_balance := calc_asg_stat_ytd_action(p_assignment_action_id,
1051                                                l_balance_type_id);
1052       Elsif l_dimension_name like '%_ASG_PROC_PTD' then
1053          l_balance := calc_asg_proc_ptd_action(p_assignment_action_id,
1054                                                l_balance_type_id);
1055       Elsif l_dimension_name like  '%_ASG_TD_ITD' then
1056          l_balance := calc_asg_td_itd_action(p_assignment_action_id,
1057                                                l_balance_type_id);
1058       Elsif l_dimension_name like '%_ASG_TRANSFER_PTD' then
1059          l_balance := calc_asg_tfr_ptd_action(p_assignment_action_id,
1060                                                l_balance_type_id);
1061       --
1062       -- added odd and even by skutteti
1063       --
1064       Elsif l_dimension_name like '%_ASG_TD_ODD_TWO_YTD' then
1065          l_balance := calc_asg_td_odd_two_ytd_action(p_assignment_action_id,
1066                                                     l_balance_type_id);
1067       Elsif l_dimension_name like '%_ASG_TD_EVEN_TWO_YTD' then
1068          l_balance := calc_asg_td_even_two_ytd_actio(p_assignment_action_id,
1069                                              l_balance_type_id);
1070       Elsif l_dimension_name like '%_PAYMENTS' then
1071          l_balance := calc_payment_action(p_assignment_action_id,
1072                                                l_balance_type_id);
1073       Elsif l_dimension_name like '%_SOE_RUN' then
1074          l_balance := calc_payment_action(p_assignment_action_id,
1075                                                l_balance_type_id);
1076       Elsif l_dimension_name like '%_PER_PTD' then
1077          --hr_utility.trace('PER - Action');
1078          l_balance := calc_per_ptd_action(p_assignment_action_id,
1079                                                l_balance_type_id);
1080       --Else for all other dimensions
1081       Else
1082          l_balance := pay_balance_pkg.get_value(p_defined_balance_id,
1083                                               p_assignment_action_id);
1084       End If;
1085 --
1086    RETURN l_balance;
1087 --
1088 END calc_all_balances;
1089 --
1090 -----------------------------------------------------------------------------
1091 --
1092 --                          CALC_ALL_BALANCES
1093 --
1094 --  This is the overloaded generic function for calculating all balances
1095 --  in Date Mode. NB Element level balances cannot be obtained from here as
1096 --  they require further context.
1097 --  This now calls the Core balance package, which could not be called directly
1098 --  from a view in date mode as core date-mode creates an asg action.
1099 -----------------------------------------------------------------------------
1100 --
1101 FUNCTION calc_all_balances(
1102          p_effective_date       IN DATE,
1103          p_assignment_id        IN NUMBER,
1104          p_defined_balance_id   IN NUMBER)
1105 --
1106 RETURN NUMBER
1107 IS
1108 --
1109     l_balance                   NUMBER;
1110     l_balance1                  NUMBER;
1111     l_balance_type_id           NUMBER;
1112     l_route_id                  NUMBER;
1113     l_dimension_name            VARCHAR2(80);
1114     l_assignment_action_id      NUMBER;
1115     l_context_name              VARCHAR2(80);
1116     l_context_value             VARCHAR2(80);
1117 --
1118     cursor get_balance_type_id(c_defined_balance_id IN NUMBER) IS
1119       select pdb.balance_type_id,
1120              pbd.dimension_name,
1121              pbd.route_id
1122       from   pay_balance_dimensions pbd,
1123              pay_defined_balances   pdb
1124       where  pdb.defined_balance_id = c_defined_balance_id
1125       and    pdb.balance_dimension_id = pbd.balance_dimension_id;
1126 --
1127     cursor get_context(p_route_id   IN NUMBER,
1128                        p_act_id     IN NUMBER,
1129                        p_context_01 IN VARCHAR2,
1130                        p_context_02 IN VARCHAR2
1131                        )
1132     is
1133        select  pca.context_value,
1134                ffc.context_name
1135         from   pay_action_contexts     pca,
1136                ff_contexts             ffc,
1137                ff_route_context_usages frc,
1138                pay_balance_dimensions  pbd
1139         where  pbd.route_id = p_route_id
1140         and    pbd.route_id = frc.route_id
1141         and    frc.context_id = ffc.context_id
1142         and    ffc.context_id = pca.context_id
1143         and    pca.assignment_action_id = p_act_id
1144         and   (ffc.context_name = p_context_01 OR ffc.context_name = p_context_02)
1145         and   (ffc.context_name <> 'SOURCE_TEXT'
1146          or   (ffc.context_name = 'SOURCE_TEXT' AND
1147              exists ( select 1
1148                       from   pay_run_results       rr,
1149                              pay_run_result_values rrv,
1150                              pay_input_values_f    piv,
1151                              pay_element_types_f   petf
1152                       where  rr.assignment_action_id = pca.assignment_action_id
1153                       and    rr.element_type_id    = petf.element_type_id
1154                       and    rr.run_result_id      = rrv.run_result_id
1155                       and    piv.input_value_id    = rrv.input_value_id
1156                       and    piv.name              = 'Reference'
1157                       and    nvl(rrv.result_value, 'Unknown') = pca.context_value
1158                       and    petf.element_name     IN
1159                       (
1160                       'CAO Scotland', 'CAO Scotland NTPP', 'CMA Scotland', 'CMA Scotland NTPP', 'Court Order',
1161                       'Court Order NTPP', 'Court Order Non Priority', 'Court Order Non Priority NTPP',
1162                       'EAS Scotland', 'EAS Scotland NTPP', 'Setup Court Order Balance'
1163                       )
1164                     )
1165               )
1166               );
1167 --
1168 BEGIN
1169 --
1170    open get_balance_type_id(p_defined_balance_id);
1171    FETCH get_balance_type_id INTO
1172          l_balance_type_id, l_dimension_name, l_route_id;
1173    CLOSE get_balance_type_id;
1174 
1175    -- begin bug fix 4311080
1176    l_assignment_action_id := get_latest_action_id(p_assignment_id, p_effective_date);
1177 
1178 /* for Bug 6262406 */
1179 /*
1180    OPEN  get_context(l_route_id, l_assignment_action_id);
1181    FETCH get_context INTO l_context_value, l_context_name;
1182    CLOSE get_context;
1183 
1184    IF l_context_name = 'SOURCE_TEXT' then
1185       pay_balance_pkg.set_context(l_context_name, l_context_value);
1186    END IF;
1187 
1188    -- end bug fix 4311080 */
1189 --
1190       If l_dimension_name like '%_ASG_YTD' then
1191          l_balance := calc_asg_ytd_date(p_assignment_id,
1192                                         l_balance_type_id,
1193           p_effective_date);
1194       Elsif l_dimension_name like '%_ASG_PROC_YTD' then
1195          l_balance := calc_asg_proc_ytd_date(p_assignment_id,
1196                                              l_balance_type_id,
1197                p_effective_date);
1198       Elsif l_dimension_name like '%_ASG_RUN' then
1199          l_balance := calc_asg_run_date(p_assignment_id,
1200                                         l_balance_type_id,
1201           p_effective_date);
1202       Elsif l_dimension_name like '%_ASG_TD_YTD' then
1203          l_balance := calc_asg_td_ytd_date(p_assignment_id,
1204                                            l_balance_type_id,
1205              p_effective_date);
1206       Elsif l_dimension_name like '%_ASG_ITD' then
1207          l_balance := calc_asg_itd_date(p_assignment_id,
1208                                         l_balance_type_id,
1209           p_effective_date);
1210       Elsif l_dimension_name like  '%_ASG_QTD' then
1211          l_balance := calc_asg_qtd_date(p_assignment_id,
1212                                         l_balance_type_id,
1213           p_effective_date);
1214       Elsif l_dimension_name like  '%_ASG_STAT_YTD' then
1215          l_balance := calc_asg_stat_ytd_date(p_assignment_id,
1216                                              l_balance_type_id,
1217                p_effective_date);
1218       Elsif l_dimension_name like '%_ASG_PROC_PTD' then
1219          l_balance := calc_asg_proc_ptd_date(p_assignment_id,
1220                                              l_balance_type_id,
1221                p_effective_date);
1222       Elsif l_dimension_name like '%_ASG_TD_ITD' then
1223          l_balance := calc_asg_td_itd_date(p_assignment_id,
1224                                            l_balance_type_id,
1225              p_effective_date);
1226       Elsif l_dimension_name like '%_ASG_TRANSFER_PTD' then
1227          l_balance := calc_asg_tfr_ptd_date(p_assignment_id,
1228                                             l_balance_type_id,
1229               p_effective_date);
1230       Elsif l_dimension_name like '%_ASG_TD_ODD_TWO_YTD' then
1231          l_balance := calc_asg_td_odd_two_ytd_date(p_assignment_id,
1232                                                l_balance_type_id,
1233                                                p_effective_date);
1234       Elsif l_dimension_name like '%_ASG_TD_EVEN_TWO_YTD' then
1235          l_balance := calc_asg_td_even_two_ytd_date(p_assignment_id,
1236                                                l_balance_type_id,
1237                                                p_effective_date);
1238       Elsif l_dimension_name like '%_PAYMENTS' then
1239          l_balance := calc_payment_date(p_assignment_id,
1240                                         l_balance_type_id,
1241           p_effective_date);
1242       Elsif l_dimension_name like '%_SOE_RUN' then
1243          l_balance := calc_payment_date(p_assignment_id,
1244                                         l_balance_type_id,
1245                                         p_effective_date);
1246       Elsif l_dimension_name like '%_PER_PTD' then
1247          --hr_utility.trace('PER - Date');
1248          l_balance := calc_per_ptd_date(p_assignment_id,
1249                                         l_balance_type_id,
1250                                         p_effective_date);
1251       /*For bug fix 4452262*/
1252 /* for Bug 6262406 */
1253       Elsif l_dimension_name like '%_PER_CO_TD_REF_ITD' or l_dimension_name like '%_PER_CO_TD_REF_PTD' then
1254         FOR J IN get_context(l_route_id, l_assignment_action_id, 'SOURCE_TEXT', 'SOURCE_TEXT')
1255         LOOP
1256            IF j.context_name = 'SOURCE_TEXT' then
1257               pay_balance_pkg.set_context(j.context_name, j.context_value);
1258            END IF;
1259            l_balance := balance(l_assignment_action_id, p_defined_balance_id, p_effective_date);
1260         END LOOP;
1261         g_balance := 0;
1262 
1263       Elsif l_dimension_name like '%_ELEMENT_ITD' or  l_dimension_name like '%_ELEMENT_PTD' or
1264             l_dimension_name like '%_ELEMENT_CO_REF_ITD' then
1265         l_balance := balance(l_assignment_action_id, p_defined_balance_id, p_effective_date);
1266         g_balance := 0;
1267 
1268 	/* For Bug 9715069 */
1269       ELSif l_dimension_name like '%_ASG_PEN_YTD' then
1270 
1271       l_balance := pay_balance_pkg.get_value(p_defined_balance_id,
1272                                             l_assignment_action_id);
1273 
1274       Else
1275          -- For all other dimensions
1276          -- latest assignment action is set at the top, so comment out this called
1277          -- l_assignment_action_id := get_latest_action_id(p_assignment_id, p_effective_date);
1278          g_balance := 0;
1279          l_balance := balance(l_assignment_action_id,
1280                               p_defined_balance_id,
1281                               p_effective_date);
1282       End If;
1283 --
1284    RETURN l_balance;
1285 --
1286 END calc_all_balances;
1287 
1288 --
1289 -----------------------------------------------------------------------------
1290 --
1291 --      CALC_PER_PTD
1292 -----------------------------------------------------------------------------
1293 --
1294 
1295 FUNCTION calc_per_ptd(
1296         p_assignment_action_id  IN NUMBER,
1297         p_balance_type_id       IN NUMBER,
1298         p_effective_date        IN DATE DEFAULT NULL,
1299         p_assignment_id   IN NUMBER)
1300 RETURN NUMBER IS
1301 --
1302         l_balance               NUMBER;
1303         l_defined_bal_id  NUMBER;
1304 --
1305 BEGIN
1306 --
1307 --Do we need to work out a value for this dimension/balance combination.
1308 --
1309   l_defined_bal_id := dimension_relevant(p_balance_type_id, '_PER_PTD');
1310   --hr_utility.trace('PER - Dimension relevant?');
1311   IF l_defined_bal_id IS NOT NULL THEN
1312     --hr_utility.trace('PER - Dimension is relevant');
1313     --
1314     -- Call core balance pkg with the defined balance just retrieved.
1315     l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
1316                                            p_assignment_action_id);
1317 
1318   ELSE
1319    --hr_utility.trace('PER - Dimension not relevant');
1320    l_balance := null;
1321   END IF;
1322   RETURN l_balance;
1323 --
1324 END calc_per_ptd;
1325 
1326 -----------------------------------------------------------------------
1327 FUNCTION calc_per_ptd_action(
1328         p_assignment_action_id  IN NUMBER,
1329         p_balance_type_id       IN NUMBER,
1330         p_effective_date        IN DATE DEFAULT NULL)
1331 RETURN NUMBER
1332 IS
1333 --
1334     l_assignment_action_id      NUMBER;
1335     l_balance                   NUMBER;
1336     l_assignment_id             NUMBER;
1337     l_action_eff_date            DATE;
1338 --
1339 BEGIN
1340 --
1341   --
1342   --  Check if assignment action is of type ('R', 'Q', 'I', 'V', 'B')
1343   --
1344   l_assignment_id := get_correct_type(p_assignment_action_id);
1345   --hr_utility.trace('PER - Ass id='||l_assignment_id );
1346   IF l_assignment_id is null THEN
1347     l_balance := null;
1348   ELSE
1349     --hr_utility.trace('PER - get bal');
1350     l_balance := calc_per_ptd(
1351                               p_assignment_action_id => p_assignment_action_id,
1352                               p_balance_type_id      => p_balance_type_id,
1353                               p_effective_date       => p_effective_date,
1354                               p_assignment_id        => l_assignment_id);
1355     --hr_utility.trace('PER - Bal='|| l_balance);
1356   END IF;
1357   --
1358   RETURN l_balance;
1359 end calc_per_ptd_action;
1360 
1361 -----------------------------------------------------------------------
1362 FUNCTION calc_per_ptd_date(
1363         p_assignment_id         IN NUMBER,
1364         p_balance_type_id       IN NUMBER,
1365         p_effective_date        IN DATE)
1366 RETURN NUMBER
1367 IS
1368 --
1369     l_assignment_action_id      NUMBER;
1370     l_balance                   NUMBER;
1371     l_end_date                  DATE;
1372     l_action_eff_date           DATE;
1373 --
1374 BEGIN
1375   --
1376   l_assignment_action_id := get_latest_action_id(p_assignment_id,
1377                p_effective_date);
1378   --hr_utility.trace('PER - Action id='||l_assignment_action_id );
1379   IF l_assignment_action_id is null then
1380      l_balance := 0;
1381   ELSE
1382     --   Chk date now
1383     l_action_eff_date := get_latest_date(l_assignment_action_id);
1384     --hr_utility.trace('PER - Action dt='||l_action_eff_date );
1385     --
1386     --   Is effective date (sess) later than the action effective date.
1387     --
1388     IF p_effective_date > l_action_eff_date THEN
1389       --hr_utility.trace('PER - Not Getting Bal');
1390       l_balance := 0;
1391     ELSE
1392       --hr_utility.trace('PER - Getting Bal');
1393       l_balance := calc_per_ptd(
1394                                 p_assignment_action_id => l_assignment_action_id,
1395                                 p_balance_type_id      => p_balance_type_id,
1396                                 p_effective_date       => p_effective_date,
1397         p_assignment_id        => p_assignment_id);
1398       --hr_utility.trace('PER - Bal='||l_balance);
1399     END IF;
1400   END IF;
1401   --
1402   RETURN l_balance;
1403 end calc_per_ptd_date;
1404 --
1405 -----------------------------------------------------------------------------
1406 ---
1407 --
1408 --                          CALC_ASG_PROC_YTD_ACTION
1409 --
1410 --    This is the function for calculating assignment year to
1411 --                      date in asg action mode
1412 --
1413 -----------------------------------------------------------------------------
1414 --
1415 FUNCTION calc_asg_proc_ytd_action(
1416          p_assignment_action_id IN NUMBER,
1417          p_balance_type_id      IN NUMBER,
1418          p_effective_date       IN DATE)
1419 RETURN NUMBER
1420 IS
1421 --
1422     l_assignment_action_id      NUMBER;
1423     l_balance                   NUMBER;
1424     l_assignment_id             NUMBER;
1425     l_effective_date            DATE;
1426 --
1427 BEGIN
1428 --
1429     l_assignment_id := get_correct_type(p_assignment_action_id);
1430     IF l_assignment_id is null THEN
1431 --
1432 --  The assignment action is not a payroll or quickpay type, so return null
1433 --
1434     l_balance := null;
1435     ELSE
1436 --
1437        l_balance := calc_asg_proc_ytd(
1438                                  p_assignment_action_id => p_assignment_action_id,
1439                                  p_balance_type_id      => p_balance_type_id,
1440                                  p_effective_date       => p_effective_date,
1441          p_assignment_id        => l_assignment_id);
1442     END IF;
1443 --
1444    RETURN l_balance;
1445 end calc_asg_proc_ytd_action;
1446 --
1447 -----------------------------------------------------------------------------
1448 ---
1449 --
1450 --                          CALC_ASG_PROC_YTD_DATE                              -
1451 --
1452 --    This is the function for calculating assignment proc year to
1453 --                      date in date mode
1454 --
1455 -----------------------------------------------------------------------------
1456 --
1457 FUNCTION calc_asg_proc_ytd_date(
1458          p_assignment_id        IN NUMBER,
1459          p_balance_type_id      IN NUMBER,
1460          p_effective_date       IN DATE)
1461 RETURN NUMBER
1462 IS
1463 --
1464     l_assignment_action_id      NUMBER;
1465     l_balance                   NUMBER;
1466     l_end_date                  DATE;
1467     l_action_eff_date           DATE;
1468 --
1469 BEGIN
1470 --
1471     l_assignment_action_id := get_latest_action_id(p_assignment_id,
1472                p_effective_date);
1473     IF l_assignment_action_id is null then
1474        l_balance := 0;
1475     ELSE
1476 --     start expiry chk now
1477        l_action_eff_date := get_latest_date(l_assignment_action_id);
1478 --
1479 --     Is effective date (sess) later than the expiry of the financial year of the
1480 --     effective date.
1481 --
1482        if p_effective_date >= get_expired_year_date(l_action_eff_date) then
1483          l_balance := 0;
1484        else
1485 --
1486        l_balance := calc_asg_proc_ytd(
1487                                  p_assignment_action_id => l_assignment_action_id,
1488                                  p_balance_type_id      => p_balance_type_id,
1489                                  p_effective_date       => p_effective_date,
1490          p_assignment_id  => p_assignment_id);
1491        end if;
1492     END IF;
1493 --
1494    RETURN l_balance;
1495 end calc_asg_proc_ytd_date;
1496 --
1497 --------------------------------------------------------------------------------
1498 --
1499 --                          CALC_ASG_PROC_YTD                                    --
1500 --  calculate balances for Assignment process year to date
1501 --
1502 --------------------------------------------------------------------------------
1503 -- Assignment Process Year -
1504 -- This dimension is the total for an assignment within the processing
1505 -- year of his current payroll, OR if the assignment has transferred
1506 -- payroll within the current processing year, it is the total since
1507 -- he joined the current payroll.
1508 
1509 -- This dimension should be used for the year dimension of balances
1510 -- which are reset to zero on transferring payroll.
1511 --
1512 FUNCTION calc_asg_proc_ytd(
1513         p_assignment_action_id  IN NUMBER,
1514         p_balance_type_id       IN NUMBER,
1515         p_effective_date        IN DATE DEFAULT NULL,
1516         p_assignment_id       IN NUMBER
1517                            )
1518 RETURN NUMBER
1519 IS
1520 --
1521         l_balance               NUMBER;
1522         l_defined_bal_id  NUMBER;
1523 --
1524 BEGIN
1525 --
1526 --Do we need to work out a value for this dimension/balance combination.
1527 --
1528  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_PROC_YTD');
1529  if l_defined_bal_id is not null then
1530    --
1531    -- Call core balance pkg with the defined balance just retrieved.
1532    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
1533                                           p_assignment_action_id);
1534    --
1535  else l_balance := null;
1536  end if;
1537    RETURN l_balance;
1538 --
1539    END calc_asg_proc_ytd;
1540 -----------------------------------------------------------------------------
1541 ---
1542 --
1543 --                          CALC_ASG_QTD_ACTION                              -
1544 --
1545 --    This is the function for calculating assignment quarter to
1546 --                      date in asg action mode
1547 --
1548 -----------------------------------------------------------------------------
1549 --
1550 FUNCTION calc_asg_qtd_action(
1551          p_assignment_action_id IN NUMBER,
1552          p_balance_type_id      IN NUMBER,
1553          p_effective_date       IN DATE)
1554 RETURN NUMBER
1555 IS
1556 --
1557     l_assignment_action_id      NUMBER;
1558     l_balance                   NUMBER;
1559     l_assignment_id             NUMBER;
1560     l_effective_date            DATE;
1561 --
1562 BEGIN
1563 --
1564     l_assignment_id := get_correct_type(p_assignment_action_id);
1565     IF l_assignment_id is null THEN
1566 --
1567 --  The assignment action is not a payroll or quickpay type, so return null
1568 --
1569        l_balance := null;
1570     ELSE
1571 --
1572        l_balance := calc_asg_qtd(
1573                                  p_assignment_action_id => p_assignment_action_id,
1574                                  p_balance_type_id      => p_balance_type_id,
1575                                  p_effective_date       => p_effective_date,
1576          p_assignment_id  => l_assignment_id);
1577     END IF;
1578 --
1579    RETURN l_balance;
1580 end calc_asg_qtd_action;
1581 --
1582 -----------------------------------------------------------------------------
1583 ---
1584 --
1585 --                          CALC_ASG_QTD_DATE                              -
1586 --
1587 --    This is the function for calculating assignment quarter
1588 --                to date in DATE MODE
1589 --
1590 -----------------------------------------------------------------------------
1591 --
1592 FUNCTION calc_asg_qtd_date(
1593          p_assignment_id        IN NUMBER,
1594          p_balance_type_id      IN NUMBER,
1595          p_effective_date       IN DATE)
1596 RETURN NUMBER
1597 IS
1598 --
1599     l_assignment_action_id      NUMBER;
1600     l_balance                   NUMBER;
1601     l_conv_us_gb_qd             DATE;
1602     l_quarter_expiry_date       DATE;
1603     l_action_eff_date           DATE;
1604 --
1605 BEGIN
1606 --
1607     l_assignment_action_id := get_latest_action_id(p_assignment_id,
1608                p_effective_date);
1609     IF l_assignment_action_id is null THEN
1610     l_balance := 0;
1611     ELSE
1612     l_balance := calc_asg_qtd(
1613                              p_assignment_action_id => l_assignment_action_id,
1614                              p_balance_type_id      => p_balance_type_id,
1615            p_effective_date       => p_effective_date,
1616                              p_assignment_id        => p_assignment_id);
1617     END IF;
1618 --
1619    RETURN l_balance;
1620 end calc_asg_qtd_date;
1621 --
1622 --------------------------------------------------------------------------------
1623 --
1624 --                          CALC_ASG_QTD                                    --
1625 --      calculate balances for Assignment Quarter to date
1626 --
1627 --------------------------------------------------------------------------------
1628 -- This dimension is the total for an assignment within the quarter. It uses
1629 --
1630 FUNCTION calc_asg_qtd(
1631         p_assignment_action_id  IN NUMBER,
1632         p_balance_type_id       IN NUMBER,
1633         p_effective_date        IN DATE DEFAULT NULL,
1634   p_assignment_id   IN NUMBER
1635                      )
1636 RETURN NUMBER
1637 IS
1638 --
1639         l_balance               NUMBER;
1640         l_defined_bal_id  NUMBER;
1641 --
1642 BEGIN
1643 --
1644 --Do we need to work out a value for this dimension/balance combination.
1645 --
1646  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_QTD');
1647  if l_defined_bal_id is not null then
1648    --
1649    -- Call core balance pkg with the defined balance just retrieved.
1650    --
1651    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
1652                                           p_assignment_action_id);
1653  end if;
1654 --
1655    RETURN l_balance;
1656 --
1657    END calc_asg_qtd;
1658 --
1659 -----------------------------------------------------------------------------
1660 ---
1661 --
1662 --                          CALC_ASG_YTD_ACTION                              -
1663 --
1664 --    This is the function for calculating assignment year to
1665 --                      date in asg action mode
1666 --
1667 -----------------------------------------------------------------------------
1668 --
1669 FUNCTION calc_asg_ytd_action(
1670          p_assignment_action_id IN NUMBER,
1671          p_balance_type_id      IN NUMBER,
1672          p_effective_date       IN DATE)
1673 RETURN NUMBER
1674 IS
1675 --
1676     l_assignment_action_id      NUMBER;
1677     l_balance                   NUMBER;
1678     l_assignment_id             NUMBER;
1679     l_effective_date      DATE;
1680 --
1681 BEGIN
1682 --
1683     l_assignment_id := get_correct_type(p_assignment_action_id);
1684     IF l_assignment_id is null THEN
1685 --
1686 --  The assignment action is not a payroll or quickpay type, so return null
1687 --
1688        l_balance := null;
1689     ELSE
1690 --
1691        l_balance := calc_asg_ytd(
1692                                  p_assignment_action_id => p_assignment_action_id,
1693                                  p_balance_type_id      => p_balance_type_id,
1694                                  p_effective_date       => p_effective_date,
1695          p_assignment_id  => l_assignment_id);
1696     END IF;
1697 --
1698    RETURN l_balance;
1699 end calc_asg_ytd_action;
1700 --
1701 -----------------------------------------------------------------------------
1702 ---
1703 --
1704 --                          CALC_ASG_YTD_DATE                              -
1705 --
1706 --    This is the function for calculating assignment year to
1707 --          date in date mode
1708 --
1709 -----------------------------------------------------------------------------
1710 --
1711 FUNCTION calc_asg_ytd_date(
1712          p_assignment_id        IN NUMBER,
1713          p_balance_type_id      IN NUMBER,
1714          p_effective_date       IN DATE)
1715 RETURN NUMBER
1716 IS
1717 --
1718     l_assignment_action_id      NUMBER;
1719     l_balance                   NUMBER;
1720     l_end_date                  DATE;
1721     l_action_eff_date   DATE;
1722 --
1723 BEGIN
1724 --
1725     l_assignment_action_id := get_latest_action_id(p_assignment_id,
1726                                                    p_effective_date);
1727     IF l_assignment_action_id is null THEN
1728        l_balance := 0;
1729     ELSE
1730 --     start expiry chk now
1731        l_action_eff_date := get_latest_date(l_assignment_action_id);
1732 --
1733 --     Is effective date (sess) later than the expiry of the financial year of the
1734 --     effective date.
1735 --
1736        if p_effective_date >= get_expired_year_date(l_action_eff_date) then
1737          l_balance := 0;
1738        else
1739 --
1740          l_balance := calc_asg_ytd(
1741                                  p_assignment_action_id => l_assignment_action_id,
1742                                  p_balance_type_id      => p_balance_type_id,
1743                                  p_effective_date       => p_effective_date,
1744                                  p_assignment_id        => p_assignment_id);
1745        end if;
1746     END IF;
1747 --
1748    RETURN l_balance;
1749 end calc_asg_ytd_date;
1750 --
1751 --------------------------------------------------------------------------------
1752 --
1753 --                          CALC_ASG_YTD                                    --
1754 --    calculate balances for Assignment year to date
1755 --      Call core balance package.
1756 --------------------------------------------------------------------------------
1757 --
1758 -- Assignment Year -
1759 --
1760 -- This dimension is the total for an assignment within the processing
1761 -- year of any payrolls he has been on this year. That is in the case
1762 -- of a transfer the span will go back to the start of the processing
1763 -- year he was on at the start of year.
1764 --
1765 -- This dimension should be used for the year dimension of balances
1766 -- which are not reset to zero on transferring payroll.
1767 -- If this has been called from the date mode function, the effective date
1768 -- will be set, otherwise session date is used.
1769 --
1770 FUNCTION calc_asg_ytd(
1771         p_assignment_action_id  IN NUMBER,
1772         p_balance_type_id       IN NUMBER,
1773         p_effective_date        IN DATE DEFAULT NULL,
1774         p_assignment_id   IN NUMBER
1775                      )
1776 RETURN NUMBER
1777 IS
1778 --
1779   l_expired_balance NUMBER;
1780         l_balance               NUMBER;
1781         l_session_date          DATE;
1782         l_assignment_id         NUMBER;
1783         l_action_eff_date       DATE;
1784         l_latest_value_exists   VARCHAR2(2);
1785         l_assignment_action_id  NUMBER;
1786         l_defined_bal_id  NUMBER;
1787 --
1788 BEGIN
1789 --
1790 -- Similar to proc yr, we need to find out firstly whether there is a
1791 -- value in latest balances, and then find out whether this can be used.
1792 -- The latest balances table is then checked again to see whether there was
1793 -- a value in the past, not necessarily for this assignment action, and whether
1794 -- it is valid.
1795 -- If not, the route code will be used to calculate the correct balance figure.
1796 --
1797 --Do we need to work out a value for this dimension/balance combination.
1798 --
1799  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_YTD');
1800  if l_defined_bal_id is not null then
1801 --
1802    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
1803                                           p_assignment_action_id);
1804 --
1805  else l_balance := null;
1806  end if;
1807 --
1808 RETURN l_balance;
1809 --
1810 END calc_asg_ytd;
1811 --
1812 -----------------------------------------------------------------------------
1813 ---
1814 --
1815 --                          CALC_ASG_STAT_YTD_ACTION                              -
1816 --
1817 --    This is the function for calculating assignment stat. year to
1818 --                      date in asg action mode
1819 --
1820 -----------------------------------------------------------------------------
1821 --
1822 FUNCTION calc_asg_stat_ytd_action(
1823          p_assignment_action_id IN NUMBER,
1824          p_balance_type_id      IN NUMBER,
1825          p_effective_date       IN DATE)
1826 RETURN NUMBER
1827 IS
1828 --
1829     l_assignment_action_id      NUMBER;
1830     l_balance                   NUMBER;
1831     l_assignment_id             NUMBER;
1832     l_effective_date      DATE;
1833 --
1834 BEGIN
1835 --
1836     l_assignment_id := get_correct_type(p_assignment_action_id);
1837     IF l_assignment_id is null THEN
1838 --
1839 --  The assignment action is not a payroll or quickpay type, so return null
1840 --
1841        l_balance := null;
1842 --
1843     ELSE
1844 --
1845        l_balance := calc_asg_stat_ytd(
1846                                  p_assignment_action_id => p_assignment_action_id,
1847                                  p_balance_type_id      => p_balance_type_id,
1848                                  p_effective_date       => p_effective_date,
1849          p_assignment_id  => l_assignment_id);
1850     END IF;
1851 --
1852    RETURN l_balance;
1853 end calc_asg_stat_ytd_action;
1854 --
1855 -----------------------------------------------------------------------------
1856 ---
1857 --
1858 --                          CALC_ASG_STAT_YTD_DATE                              -
1859 --
1860 --    This is the function for calculating assignment stat. year to
1861 --                      date in date mode
1862 --
1863 -----------------------------------------------------------------------------
1864 --
1865 FUNCTION calc_asg_stat_ytd_date(
1866          p_assignment_id        IN NUMBER,
1867          p_balance_type_id      IN NUMBER,
1868          p_effective_date       IN DATE)
1869 RETURN NUMBER
1870 IS
1871 --
1872     l_assignment_action_id      NUMBER;
1873     l_balance                   NUMBER;
1874     l_end_date                  DATE;
1875     l_action_eff_date           DATE;
1876 --
1877 BEGIN
1878 --
1879     l_assignment_action_id := get_latest_action_id(p_assignment_id,
1880                                                    p_effective_date);
1881     IF l_assignment_action_id is null THEN
1882        l_balance := 0;
1883     ELSE
1884 --     start expiry chk now
1885        l_action_eff_date := get_latest_date(l_assignment_action_id);
1886 --
1887 --     Is effective date (sess) later than the expiry of the financial year of the
1888 --     effective date.
1889 --
1890        if p_effective_date >= get_expired_year_date(l_action_eff_date) then
1891          l_balance := 0;
1892        else
1893 --
1894        l_balance := calc_asg_stat_ytd(
1895                                  p_assignment_action_id => l_assignment_action_id,
1896                                  p_balance_type_id      => p_balance_type_id,
1897                                  p_effective_date       => p_effective_date,
1898                                  p_assignment_id        => p_assignment_id);
1899        end if;
1900     END IF;
1901 --
1902    RETURN l_balance;
1903 end calc_asg_stat_ytd_date;
1904 --
1905 --------------------------------------------------------------------------------
1906 --
1907 --                          CALC_ASG_STAT_YTD                                    --
1908 --      calculate balances for Assignment stat year to date
1909 --
1910 --------------------------------------------------------------------------------
1911 --
1912 -- This dimension is the total for an assignment within the statutory
1913 -- year (since the previous 6th April)of any payrolls he has been on this year
1914 --
1915 FUNCTION calc_asg_stat_ytd(
1916         p_assignment_action_id  IN NUMBER,
1917         p_balance_type_id       IN NUMBER,
1918         p_effective_date        IN DATE DEFAULT NULL,
1919   p_assignment_id   IN NUMBER
1920                      )
1921 RETURN NUMBER
1922 IS
1923 --
1924   l_expired_balance NUMBER;
1925         l_balance               NUMBER;
1926         l_session_date          DATE;
1927         l_assignment_id         NUMBER;
1928         l_action_eff_date       DATE;
1929         l_latest_value_exists   VARCHAR2(2);
1930         l_assignment_action_id  NUMBER;
1931         l_defined_bal_id  NUMBER;
1932 --
1933 BEGIN
1934 --
1935 --Do we need to work out a value for this dimension/balance combination.
1936 --
1937  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_STAT_YTD');
1938  if l_defined_bal_id is not null then
1939 --
1940    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
1941                                           p_assignment_action_id);
1942 --
1943  else l_balance := null;
1944  end if;
1945 --
1946 RETURN l_balance;
1947 --
1948 END calc_asg_stat_ytd;
1949 --
1950 -----------------------------------------------------------------------------
1951 ---
1952 --
1953 --                          CALC_ASG_PROC_PTD_ACTION
1954 --
1955 --         This is the function for calculating assignment
1956 --          proc. period to date in assignment action mode
1957 --
1958 -----------------------------------------------------------------------------
1959 --
1960 FUNCTION calc_asg_proc_ptd_action(
1961          p_assignment_action_id IN NUMBER,
1962          p_balance_type_id      IN NUMBER,
1963          p_effective_date       IN DATE)
1964 RETURN NUMBER
1965 IS
1966 --
1967     l_assignment_action_id      NUMBER;
1968     l_balance                   NUMBER;
1969     l_assignment_id             NUMBER;
1970     l_effective_date    DATE;
1971 --
1972 BEGIN
1973 --
1974     l_assignment_id := get_correct_type(p_assignment_action_id);
1975     IF l_assignment_id is null THEN
1976 --
1977 --  The assignment action is not a payroll or quickpay type, so return null
1978 --
1979        l_balance := null;
1980     ELSE
1981 --
1982        l_balance := calc_asg_proc_ptd(
1983                                  p_assignment_action_id => p_assignment_action_id
1984 ,
1985                                  p_balance_type_id      => p_balance_type_id,
1986                                  p_effective_date       => p_effective_date,
1987          p_assignment_id  => l_assignment_id);
1988     END IF;
1989 --
1990    RETURN l_balance;
1991 end calc_asg_proc_ptd_action;
1992 --
1993 -----------------------------------------------------------------------------
1994 ---
1995 --
1996 --                          CALC_ASG_PROC_PTD_DATE
1997 --
1998 --    This is the function for calculating assignment processing
1999 --    period to date in date mode
2000 --
2001 -----------------------------------------------------------------------------
2002 --
2003 FUNCTION calc_asg_proc_ptd_date(
2004          p_assignment_id        IN NUMBER,
2005          p_balance_type_id      IN NUMBER,
2006          p_effective_date       IN DATE)
2007 RETURN NUMBER
2008 IS
2009 --
2010     l_assignment_action_id      NUMBER;
2011     l_balance                   NUMBER;
2012     l_period_end_date           DATE;
2013     l_date_paid                 DATE;
2014 --
2015 -- Has the processing time period expired
2016 --
2017    cursor expired_time_period (c_assignment_action_id IN NUMBER) is
2018     SELECT ptp.end_date, ppa.effective_date
2019     FROM per_time_periods ptp,
2020          pay_payroll_actions ppa,
2021          pay_assignment_actions paa
2022     WHERE
2023          paa.assignment_action_id = c_assignment_action_id
2024     AND  paa.payroll_action_id = ppa.payroll_action_id
2025     AND  ppa.time_period_id = ptp.time_period_id;
2026 --
2027 BEGIN
2028 --
2029     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2030                                                    p_effective_date);
2031     IF l_assignment_action_id is null THEN
2032        l_balance := 0;
2033     ELSE
2034        open expired_time_period(l_assignment_action_id);
2035        FETCH expired_time_period INTO l_period_end_date, l_date_paid;
2036        close expired_time_period;
2037 --
2038        if greatest(l_period_end_date,l_date_paid) < p_effective_date then
2039           l_balance := 0;
2040        else
2041           l_balance := calc_asg_proc_ptd(
2042                              p_assignment_action_id => l_assignment_action_id,
2043                              p_balance_type_id      => p_balance_type_id,
2044                              p_effective_date       => p_effective_date,
2045                              p_assignment_id        => p_assignment_id);
2046        end if;
2047     END IF;
2048 --
2049    RETURN l_balance;
2050 end calc_asg_proc_ptd_date;
2051 --
2052 -----------------------------------------------------------------------------
2053 ---
2054 --
2055 --                          CALC_ASG_PROC_PTD                              -
2056 --      calculate balances for Assignment process period to date
2057 --      Calls Core Balance pkg.
2058 --
2059 -----------------------------------------------------------------------------
2060 ---
2061 --
2062 -- This dimension is the total for an assignment within the processing
2063 -- period of his current payroll, OR if the assignment has transferred
2064 -- payroll within the current processing period, it is the total since
2065 -- he joined the current payroll.
2066 --
2067 -- This dimension should be used for the period dimension of balances
2068 -- which are reset to zero on transferring payroll.
2069 --
2070 FUNCTION calc_asg_proc_ptd(
2071         p_assignment_action_id  IN NUMBER,
2072         p_balance_type_id       IN NUMBER,
2073         p_effective_date        IN DATE DEFAULT NULL,
2074   p_assignment_id   IN NUMBER
2075                           )
2076 --
2077 RETURN NUMBER
2078 IS
2079 --
2080 --
2081   l_expired_balance NUMBER;
2082   l_assignment_action_id  NUMBER;
2083         l_balance               NUMBER;
2084         l_latest_value_exists   VARCHAR2(2);
2085   l_action_eff_date DATE;
2086   l_end_date    DATE;
2087       l_defined_bal_id  NUMBER;
2088 --
2089 BEGIN
2090 --
2091 --Do we need to work out a value for this dimension/balance combination.
2092 --
2093  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_PROC_PTD');
2094  if l_defined_bal_id is not null then
2095 --
2096    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2097                                           p_assignment_action_id);
2098 --
2099  else l_balance := null;
2100  end if;
2101 --
2102 RETURN l_balance;
2103 --
2104 END calc_asg_proc_ptd;
2105 --
2106 --
2107 -----------------------------------------------------------------------------
2108 ---
2109 --
2110 --                          CALC_ASG_RUN_ACTION                              -
2111 --
2112 --         This is the function for calculating assignment
2113 --                runs in assignment action mode
2114 --
2115 -----------------------------------------------------------------------------
2116 --
2117 FUNCTION calc_asg_run_action(
2118          p_assignment_action_id IN NUMBER,
2119          p_balance_type_id      IN NUMBER,
2120          p_effective_date       IN DATE)
2121 RETURN NUMBER
2122 IS
2123 --
2124     l_assignment_action_id      NUMBER;
2125     l_balance                   NUMBER;
2126     l_assignment_id             NUMBER;
2127     l_effective_date          DATE;
2128 --
2129 BEGIN
2130 --
2131     l_assignment_id := get_correct_type(p_assignment_action_id);
2132     IF l_assignment_id is null THEN
2133 --
2134 --  The assignment action is not a payroll or quickpay type, so return null
2135 --
2136        l_balance := null;
2137     ELSE
2138 --
2139        l_balance := calc_asg_run(
2140                                  p_assignment_action_id => p_assignment_action_id
2141 ,
2142                                  p_balance_type_id      => p_balance_type_id,
2143                                  p_effective_date       => p_effective_date,
2144          p_assignment_id  => l_assignment_id);
2145     END IF;
2146 --
2147    RETURN l_balance;
2148 end calc_asg_run_action;
2149 --
2150 -----------------------------------------------------------------------------
2151 ---
2152 --
2153 --                          CALC_ASG_RUN_DATE                              -
2154 --
2155 --    This is the function for calculating assignment run in
2156 --                DATE MODE
2157 --
2158 -----------------------------------------------------------------------------
2159 --
2160 FUNCTION calc_asg_run_date(
2161          p_assignment_id  IN NUMBER,
2162          p_balance_type_id      IN NUMBER,
2163          p_effective_date       IN DATE)
2164 RETURN NUMBER
2165 IS
2166 --
2167     l_assignment_action_id  NUMBER;
2168     l_balance     NUMBER;
2169     l_period_end_date           DATE;
2170     l_date_paid                 DATE;
2171 --
2172    cursor expired_time_period (c_assignment_action_id IN NUMBER) is
2173     SELECT ptp.end_date, ppa.effective_date
2174     FROM per_time_periods ptp,
2175          pay_payroll_actions ppa,
2176          pay_assignment_actions paa
2177     WHERE
2178          paa.assignment_action_id = c_assignment_action_id
2179     AND  paa.payroll_action_id = ppa.payroll_action_id
2180     AND  ppa.time_period_id = ptp.time_period_id;
2181 --
2182 BEGIN
2183 --
2184     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2185                                                    p_effective_date);
2186     IF l_assignment_action_id is null THEN
2187        l_balance := 0;
2188     ELSE
2189        open expired_time_period(l_assignment_action_id);
2190        FETCH expired_time_period INTO l_period_end_date, l_date_paid;
2191        close expired_time_period;
2192 --
2193        if greatest(l_period_end_date,l_date_paid) < p_effective_date then
2194           l_balance := 0;
2195        else
2196           l_balance := calc_asg_run(
2197                              p_assignment_action_id => l_assignment_action_id,
2198            p_balance_type_id      => p_balance_type_id,
2199                              p_effective_date       => p_effective_date,
2200                              p_assignment_id        => p_assignment_id);
2201        end if;
2202     END IF;
2203 --
2204    RETURN l_balance;
2205 end calc_asg_run_date;
2206 --
2207 -----------------------------------------------------------------------------
2208 ---
2209 --
2210 --                          CALC_ASG_RUN                              -
2211 --      calculate balances for Assignment Run . Now calls core package.
2212 --
2213 -----------------------------------------------------------------------------
2214 --
2215 -- Run
2216 --    the simplest dimension retrieves run values where the context
2217 --    is this assignment action and this balance feed. Balance is the
2218 --    specified input value. The related payroll action determines the
2219 --    date effectivity of the feeds
2220 --
2221 FUNCTION calc_asg_run(
2222         p_assignment_action_id  IN NUMBER,
2223         p_balance_type_id       IN NUMBER,
2224         p_effective_date        IN DATE DEFAULT NULL,
2225   p_assignment_id   IN NUMBER
2226                      )
2227 RETURN NUMBER
2228 IS
2229 --
2230 --
2231         l_balance               NUMBER;
2232   l_defined_bal_id  NUMBER;
2233 --
2234 BEGIN
2235 --
2236 --Do we need to work out a value for this dimension/balance combination.
2237 --
2238  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_RUN');
2239  if l_defined_bal_id is not null then
2240 --
2241 -- Call core balance pkg with the defined balance just retrieved.
2242 --
2243    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2244                                           p_assignment_action_id);
2245 --
2246  else l_balance := null;
2247  end if;
2248 --
2249 RETURN l_balance;
2250 --
2251 END calc_asg_run;
2252 --
2253 -----------------------------------------------------------------------------
2254 --
2255 --                          CALC_PAYMENT_ACTION                              -
2256 --
2257 --         This is the function for calculating payments
2258 --                in assignment action mode
2259 -----------------------------------------------------------------------------
2260 --
2261 FUNCTION calc_payment_action(
2262          p_assignment_action_id IN NUMBER,
2263          p_balance_type_id      IN NUMBER,
2264          p_effective_date       IN DATE)
2265 RETURN NUMBER
2266 IS
2267 --
2268     l_assignment_action_id      NUMBER;
2269     l_balance                   NUMBER;
2270     l_assignment_id             NUMBER;
2271     l_effective_date    DATE;
2272 --
2273 BEGIN
2274 --
2275     l_assignment_id := get_correct_type(p_assignment_action_id);
2276     IF l_assignment_id is null THEN
2277 --
2278 --  The assignment action is not a payroll or quickpay type, so return null
2279 --
2280        l_balance := null;
2281     ELSE
2282 --
2283        l_balance := calc_payment(
2284                                  p_assignment_action_id => p_assignment_action_id
2285 ,
2286                                  p_balance_type_id      => p_balance_type_id,
2287                                  p_effective_date       => p_effective_date,
2288          p_assignment_id  => l_assignment_id);
2289     END IF;
2290 --
2291    RETURN l_balance;
2292 end calc_payment_action;
2293 --
2294 -----------------------------------------------------------------------------
2295 --
2296 --                          CALC_PAYMENT_DATE                              -
2297 --
2298 --    This is the function for calculating payments in
2299 --                            DATE MODE
2300 -----------------------------------------------------------------------------
2301 --
2302 FUNCTION calc_payment_date(
2303          p_assignment_id        IN NUMBER,
2304          p_balance_type_id      IN NUMBER,
2305          p_effective_date       IN DATE)
2306 RETURN NUMBER
2307 IS
2308 --
2309     l_assignment_action_id      NUMBER;
2310     l_balance                   NUMBER;
2311     l_period_end_date           DATE;
2312     l_date_paid                 DATE;
2313 --
2314    cursor expired_time_period (c_assignment_action_id IN NUMBER) is
2315     SELECT ptp.end_date, ppa.effective_date
2316     FROM per_time_periods ptp,
2317          pay_payroll_actions ppa,
2318          pay_assignment_actions paa
2319     WHERE
2320          paa.assignment_action_id = c_assignment_action_id
2321     AND  paa.payroll_action_id = ppa.payroll_action_id
2322     AND  ppa.time_period_id = ptp.time_period_id;
2323 --
2324 BEGIN
2325 --
2326     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2327                                                    p_effective_date);
2328     IF l_assignment_action_id is null THEN
2329        l_balance := 0;
2330     ELSE
2331        open expired_time_period(l_assignment_action_id);
2332        FETCH expired_time_period INTO l_period_end_date, l_date_paid;
2333        close expired_time_period;
2334 --
2335        if greatest(l_period_end_date,l_date_paid) < p_effective_date then
2336           l_balance := 0;
2337        else
2338           l_balance := calc_payment(
2339                              p_assignment_action_id => l_assignment_action_id,
2340                              p_balance_type_id      => p_balance_type_id,
2341                              p_effective_date       => p_effective_date,
2342                              p_assignment_id        => p_assignment_id);
2343           end if;
2344     END IF;
2345 --
2346    RETURN l_balance;
2347 end calc_payment_date;
2348 --
2349 -----------------------------------------------------------------------------
2350 --
2351 --                          CALC_PAYMENT                              -
2352 --
2353 --      calculate balances for payments . Now calls core package.
2354 -----------------------------------------------------------------------------
2355 --
2356 -- this dimension is used in the pre-payments process - that process
2357 -- creates interlocks for the actions that are included and the payments
2358 -- dimension uses those interlocks to decide which run results to sum
2359 --
2360 --
2361 FUNCTION calc_payment(
2362         p_assignment_action_id  IN NUMBER,
2363         p_balance_type_id       IN NUMBER,
2364         p_effective_date        IN DATE DEFAULT NULL,
2365   p_assignment_id   IN NUMBER
2366                      )
2367 RETURN NUMBER
2368 IS
2369 --
2370         l_balance               NUMBER;
2371         l_latest_value_exists   VARCHAR2(2);
2372         l_assignment_action_id  NUMBER;
2373   l_action_eff_date DATE;
2374   l_end_date    DATE;
2375   l_defined_bal_id  NUMBER;
2376 --
2377 BEGIN
2378 --
2379 --Do we need to work out a value for this dimension/balance combination.
2380 --
2381  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_PAYMENTS');
2382  if l_defined_bal_id is not null then
2383 --
2384    -- Call core balance pkg with the defined balance just retrieved.
2385    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2386                                           p_assignment_action_id);
2387 --
2388  else l_balance := null;
2389  end if;
2390 --
2391 RETURN l_balance;
2392 --
2393 END calc_payment;
2394 --
2395 -----------------------------------------------------------------------------
2396 --
2397 --                          CALC_ASG_ITD_ACTION                              -
2398 --
2399 --         This is the function for calculating assignment
2400 --         Inception to date in assignment action mode
2401 -----------------------------------------------------------------------------
2402 --
2403 FUNCTION calc_asg_itd_action(
2404          p_assignment_action_id IN NUMBER,
2405          p_balance_type_id      IN NUMBER,
2406          p_effective_date       IN DATE)
2407 RETURN NUMBER
2408 IS
2409 --
2410     l_assignment_action_id      NUMBER;
2411     l_balance                   NUMBER;
2412     l_assignment_id             NUMBER;
2413     l_effective_date    DATE;
2414 --
2415 BEGIN
2416 --
2417     l_assignment_id := get_correct_type(p_assignment_action_id);
2418     IF l_assignment_id is null THEN
2419 --
2420 --  The assignment action is not a payroll or quickpay type, so return null
2421 --
2422        l_balance := null;
2423     ELSE
2424 --
2425        l_balance := calc_asg_itd(p_assignment_id  => l_assignment_id,
2426                                  p_assignment_action_id => p_assignment_action_id,
2427                                  p_balance_type_id      => p_balance_type_id,
2428                                  p_effective_date       => p_effective_date);
2429     END IF;
2430 --
2431    RETURN l_balance;
2432 end calc_asg_itd_action;
2433 --
2434 -----------------------------------------------------------------------------
2435 --
2436 --                          CALC_ASG_ITD_DATE                              -
2437 --
2438 --    This is the function for calculating assignment inception to
2439 --                      date in DATE MODE
2440 -----------------------------------------------------------------------------
2441 --
2442 FUNCTION calc_asg_itd_date(
2443          p_assignment_id        IN NUMBER,
2444          p_balance_type_id      IN NUMBER,
2445          p_effective_date       IN DATE)
2446 RETURN NUMBER
2447 IS
2448 --
2449     l_assignment_action_id      NUMBER;
2450     l_balance                   NUMBER;
2451     l_end_date                  DATE;
2452 --
2453 BEGIN
2454 --
2455     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2456                                                    p_effective_date);
2457     IF l_assignment_action_id is null THEN
2458        l_balance := 0;
2459     ELSE
2460        l_balance := calc_asg_itd(
2461            p_assignment_id      => p_assignment_id,
2462                              p_assignment_action_id => l_assignment_action_id,
2463                              p_balance_type_id      => p_balance_type_id,
2464                              p_effective_date       => p_effective_date);
2465     END IF;
2466 --
2467    RETURN l_balance;
2468 end calc_asg_itd_date;
2469 --
2470 -----------------------------------------------------------------------------
2471 --
2472 --                          CALC_ASG_ITD                              -
2473 --
2474 --      calculate balances for Assignment Inception to Date
2475 -----------------------------------------------------------------------------
2476 --
2477 -- Sum of all run items since inception.
2478 --
2479 FUNCTION calc_asg_itd(
2480   p_assignment_id   IN NUMBER,
2481         p_assignment_action_id  IN NUMBER,
2482         p_balance_type_id       IN NUMBER,
2483         p_effective_date        IN DATE DEFAULT NULL -- in for consistency
2484                       )
2485 RETURN NUMBER
2486 IS
2487 --
2488 --
2489         l_balance               NUMBER;
2490         l_latest_value_exists   VARCHAR2(2);
2491     l_assignment_action_id  NUMBER;
2492   l_action_eff_date DATE;
2493   l_defined_bal_id  NUMBER;
2494 --
2495 BEGIN
2496 --
2497 --Do we need to work out a value for this dimension/balance combination.
2498 --
2499  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_ITD');
2500  if l_defined_bal_id is not null then
2501 --
2502 -- Is there a value in the latest balances table ..
2503 --
2504    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2505                                           p_assignment_action_id);
2506 --
2507  else l_balance := null;
2508  end if;
2509 --
2510 RETURN l_balance;
2511 --
2512 END calc_asg_itd;
2513 --
2514 --
2515 -----------------------------------------------------------------------------
2516 --
2517 --                          CALC_ASG_TD_ITD_ACTION                              -
2518 --
2519 --         This is the function for calculating assignment tax district
2520 --         Inception to date in assignment action mode
2521 -----------------------------------------------------------------------------
2522 --
2523 FUNCTION calc_asg_td_itd_action(
2524          p_assignment_action_id IN NUMBER,
2525          p_balance_type_id      IN NUMBER,
2526          p_effective_date       IN DATE)
2527 RETURN NUMBER
2528 IS
2529 --
2530     l_assignment_action_id      NUMBER;
2531     l_balance                   NUMBER;
2532     l_assignment_id             NUMBER;
2533     l_effective_date    DATE;
2534 --
2535 BEGIN
2536 --
2537     l_assignment_id := get_correct_type(p_assignment_action_id);
2538     IF l_assignment_id is null THEN
2539 --
2540 --  The assignment action is not a payroll or quickpay type, so return null
2541 --
2542        l_balance := null;
2543     ELSE
2544 --
2545        l_balance := calc_asg_td_itd(p_assignment_id => l_assignment_id,
2546                                  p_assignment_action_id => p_assignment_action_id,
2547                                  p_balance_type_id      => p_balance_type_id,
2548                                  p_effective_date       => p_effective_date);
2549     END IF;
2550 --
2551    RETURN l_balance;
2552 end calc_asg_td_itd_action;
2553 --
2554 -----------------------------------------------------------------------------
2555 --
2556 --                          CALC_ASG_TD_ITD_DATE                              -
2557 --
2558 --    This is the function for calculating assignment inception tax district
2559 --                      to date in DATE MODE
2560 -----------------------------------------------------------------------------
2561 --
2562 FUNCTION calc_asg_td_itd_date(
2563          p_assignment_id        IN NUMBER,
2564          p_balance_type_id      IN NUMBER,
2565          p_effective_date       IN DATE)
2566 RETURN NUMBER
2567 IS
2568 --
2569     l_assignment_action_id      NUMBER;
2570     l_balance                   NUMBER;
2571     l_end_date                  DATE;
2572 --
2573 BEGIN
2574 --
2575     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2576                                                    p_effective_date);
2577     IF l_assignment_action_id is null THEN
2578        l_balance := 0;
2579     ELSE
2580        l_balance := calc_asg_td_itd(p_assignment_id => p_assignment_id,
2581                              p_assignment_action_id => l_assignment_action_id,
2582                              p_balance_type_id      => p_balance_type_id,
2583                              p_effective_date       => p_effective_date);
2584     END IF;
2585 --
2586    RETURN l_balance;
2587 end calc_asg_td_itd_date;
2588 --
2589 -----------------------------------------------------------------------------
2590 --
2591 --                          CALC_ASG_TD_ITD                              -
2592 --
2593 --      calculate balances for Assignment tax district Inception to Date
2594 --      Calls Core Balance pkg.
2595 -----------------------------------------------------------------------------
2596 --
2597 -- Sum of all run items since inception (tax district)
2598 --
2599 FUNCTION calc_asg_td_itd(
2600   p_assignment_id   IN NUMBER,
2601         p_assignment_action_id  IN NUMBER,
2602         p_balance_type_id       IN NUMBER,
2603         p_effective_date        IN DATE DEFAULT NULL -- in for consistency
2604                       )
2605 RETURN NUMBER
2606 IS
2607 --
2608         l_balance               NUMBER;
2609   l_defined_bal_id  NUMBER;
2610 --
2611 BEGIN
2612 --
2613 --Do we need to work out a value for this dimension/balance combination.
2614 --
2615  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_TD_ITD');
2616  if l_defined_bal_id is not null then
2617    --
2618    -- Call core balance pkg with the defined balance just retrieved.
2619    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2620                                           p_assignment_action_id);
2621    --
2622  else l_balance := null;
2623  end if;
2624 --
2625 RETURN l_balance;
2626 --
2627 END calc_asg_td_itd;
2628 --
2629 -----------------------------------------------------------------------------
2630 --
2631 --                          CALC_ASG_TFR_PTD_ACTION
2632 --
2633 --         This is the function for calculating assignment
2634 --          transfer period to date in assignment action mode
2635 -----------------------------------------------------------------------------
2636 --
2637 FUNCTION calc_asg_tfr_ptd_action(
2638          p_assignment_action_id IN NUMBER,
2639          p_balance_type_id      IN NUMBER,
2640          p_effective_date       IN DATE)
2641 RETURN NUMBER
2642 IS
2643 --
2644     l_assignment_action_id      NUMBER;
2645     l_balance                   NUMBER;
2646     l_assignment_id             NUMBER;
2647     l_effective_date    DATE;
2648 --
2649 BEGIN
2650 --
2651     l_assignment_id := get_correct_type(p_assignment_action_id);
2652     IF l_assignment_id is null THEN
2653 --
2654 --  The assignment action is not a payroll or quickpay type, so return null
2655 --
2656        l_balance := null;
2657     ELSE
2658 --
2659        l_balance := calc_asg_tfr_ptd(
2660                                  p_assignment_action_id => p_assignment_action_id
2661 ,
2662                                  p_balance_type_id      => p_balance_type_id,
2663                                  p_effective_date       => p_effective_date,
2664          p_assignment_id  => l_assignment_id);
2665     END IF;
2666 --
2667    RETURN l_balance;
2668 end calc_asg_tfr_ptd_action;
2669 --
2670 -----------------------------------------------------------------------------
2671 --
2672 --                          CALC_ASG_TFR_PTD_DATE
2673 --
2674 --    This is the function for calculating assignment transfer
2675 --    period to date in date mode
2676 -----------------------------------------------------------------------------
2677 --
2678 FUNCTION calc_asg_tfr_ptd_date(
2679          p_assignment_id        IN NUMBER,
2680          p_balance_type_id      IN NUMBER,
2681          p_effective_date       IN DATE)
2682 RETURN NUMBER
2683 IS
2684 --
2685     l_assignment_action_id      NUMBER;
2686     l_balance                   NUMBER;
2687     l_period_end_date           DATE;
2688     l_date_paid                 DATE;
2689 --
2690 -- Has the processing time period expired
2691 --
2692    cursor expired_time_period (c_assignment_action_id IN NUMBER) is
2693     SELECT ptp.end_date, ppa.effective_date
2694     FROM per_time_periods ptp,
2695          pay_payroll_actions ppa,
2696          pay_assignment_actions paa
2697     WHERE
2698          paa.assignment_action_id = c_assignment_action_id
2699     AND  paa.payroll_action_id = ppa.payroll_action_id
2700     AND  ppa.time_period_id = ptp.time_period_id;
2701 --
2702 BEGIN
2703 --
2704     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2705                                                    p_effective_date);
2706     IF l_assignment_action_id is null THEN
2707        l_balance := 0;
2708     ELSE
2709        open expired_time_period(l_assignment_action_id);
2710        FETCH expired_time_period INTO l_period_end_date, l_date_paid;
2711        close expired_time_period;
2712 --
2713        if greatest(l_period_end_date,l_date_paid) < p_effective_date then
2714           l_balance := 0;
2715        else
2716           l_balance := calc_asg_tfr_ptd(
2717                              p_assignment_action_id => l_assignment_action_id,
2718                              p_balance_type_id      => p_balance_type_id,
2719                              p_effective_date       => p_effective_date,
2720                              p_assignment_id        => p_assignment_id);
2721        end if;
2722     END IF;
2723 --
2724    RETURN l_balance;
2725 end calc_asg_tfr_ptd_date;
2726 --
2727 --------------------------------------------------------------------------------
2728 --
2729 --                          CALC_ASG_TFR_PTD                                   --
2730 --    calculate Assignment transfer period to date
2731 --              Call the Core Balance function
2732 --------------------------------------------------------------------------------
2733 --
2734 --
2735 -- This dimension is the total for an assignment within the processing
2736 -- period of his current payroll, OR if the assignment has transferred
2737 -- payroll it includes run results generated from actions that are
2738 -- within the same statutory period.
2739 -- The start of the statutory period is based on a fixed calendar which
2740 -- begins on the 6th April of each calendar year. Monthly periods
2741 -- start at the 6th of each month, weekly based periods are at 7 day
2742 -- intervals from the 6th April.
2743 -- The regular payment date for the payroll period determines which
2744 -- statutory period it is in so the statutory start of period is
2745 -- compared against the regular payment date of the payroll period
2746 -- that the actions were created for.
2747 --
2748 FUNCTION calc_asg_tfr_ptd(
2749         p_assignment_action_id  IN NUMBER,
2750         p_balance_type_id       IN NUMBER,
2751         p_effective_date        IN DATE DEFAULT NULL,
2752   p_assignment_id   IN NUMBER
2753                       )
2754 RETURN NUMBER
2755 IS
2756 --
2757         l_balance               NUMBER;
2758         l_assignment_action_id  NUMBER;
2759   l_action_eff_date DATE;
2760   l_defined_bal_id  NUMBER;
2761 --
2762 BEGIN
2763 --
2764 --Do we need to work out a value for this dimension/balance combination.
2765 --
2766  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_TRANSFER_PTD');
2767  if l_defined_bal_id is not null then
2768 --
2769    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2770                                           p_assignment_action_id);
2771 --
2772  else l_balance := null;
2773  end if;
2774 --
2775 RETURN l_balance;
2776 --
2777 END calc_asg_tfr_ptd;
2778 --
2779 -----------------------------------------------------------------------------
2780 --
2781 --                          CALC_ASG_TD_YTD_ACTION                              -
2782 --
2783 --    This is the function for calculating assignment td year to
2784 --                      date in asg action mode
2785 -----------------------------------------------------------------------------
2786 --
2787 FUNCTION calc_asg_td_ytd_action(
2788          p_assignment_action_id IN NUMBER,
2789          p_balance_type_id      IN NUMBER,
2790          p_effective_date       IN DATE)
2791 RETURN NUMBER
2792 IS
2793 --
2794     l_assignment_action_id      NUMBER;
2795     l_balance                   NUMBER;
2796     l_assignment_id             NUMBER;
2797     l_effective_date    DATE;
2798 --
2799 BEGIN
2800 --
2801     l_assignment_id := get_correct_type(p_assignment_action_id);
2802     IF l_assignment_id is null THEN
2803 --
2804 --  The assignment action is not a payroll or quickpay type, so return null
2805 --
2806        l_balance := null;
2807     ELSE
2808 --
2809        l_balance := calc_asg_td_ytd(
2810                                  p_assignment_action_id => p_assignment_action_id,
2811                                  p_balance_type_id      => p_balance_type_id,
2812                                  p_effective_date       => p_effective_date,
2813          p_assignment_id  => l_assignment_id);
2814     END IF;
2815 --
2816    RETURN l_balance;
2817 end calc_asg_td_ytd_action;
2818 --
2819 ------------------------------------------------------------------------------
2820 --
2821 --      CALC_ASG_TD_YTD
2822 --  This function is for assignment tax district year to date
2823 --      Calls core balance package
2824 ------------------------------------------------------------------------------
2825 --
2826 FUNCTION calc_asg_td_ytd(
2827         p_assignment_action_id  IN NUMBER,
2828         p_balance_type_id       IN NUMBER,
2829         p_effective_date        IN DATE DEFAULT NULL,
2830   p_assignment_id   IN NUMBER
2831                      )
2832 RETURN NUMBER
2833 IS
2834 --
2835 --
2836         l_balance               NUMBER;
2837         l_session_date          DATE;
2838         l_action_eff_date       DATE;
2839         l_expired_balance       NUMBER;
2840         l_assignment_id         NUMBER;
2841         l_assignment_action_id  NUMBER;
2842         l_latest_value_exists   VARCHAR2(2);
2843   l_defined_bal_id  NUMBER;
2844 --
2845    BEGIN
2846 --
2847 --Do we need to work out a value for this dimension/balance combination.
2848 --
2849  l_defined_bal_id := dimension_relevant(p_balance_type_id, '_ASG_TD_YTD');
2850  if l_defined_bal_id is not null then
2851 --
2852    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
2853                                           p_assignment_action_id);
2854 --
2855  else l_balance := null;
2856  end if;
2857 --
2858 RETURN l_balance;
2859 --
2860 END calc_asg_td_ytd;
2861 --
2862 -----------------------------------------------------------------------------
2863 --
2864 --                          CALC_ASG_TD_YTD_DATE                              -
2865 --
2866 --    This is the function for calculating assignment year to
2867 --                      date in date mode
2868 -----------------------------------------------------------------------------
2869 --
2870 FUNCTION calc_asg_td_ytd_date(
2871          p_assignment_id        IN NUMBER,
2872          p_balance_type_id      IN NUMBER,
2873          p_effective_date       IN DATE)
2874 RETURN NUMBER
2875 IS
2876 --
2877     l_assignment_action_id      NUMBER;
2878     l_balance                   NUMBER;
2879     l_end_date                  DATE;
2880     l_action_eff_date           DATE;
2881 --
2882 BEGIN
2883 --
2884     l_assignment_action_id := get_latest_action_id(p_assignment_id,
2885                                                    p_effective_date);
2886     IF l_assignment_action_id is null THEN
2887        l_balance := 0;
2888     ELSE
2889 --     start expiry chk now
2890        l_action_eff_date := get_latest_date(l_assignment_action_id);
2891 --
2892 --     Is effective date (sess) later than the expiry of the financial year of the
2893 --     effective date.
2894 --
2895        if p_effective_date >= get_expired_year_date(l_action_eff_date) then
2896          l_balance := 0;
2897        else
2898 --
2899        l_balance := calc_asg_td_ytd(
2900                                  p_assignment_action_id => l_assignment_action_id,
2901                                  p_balance_type_id      => p_balance_type_id,
2902                                  p_effective_date       => p_effective_date,
2903                                  p_assignment_id        => p_assignment_id);
2904        end if;
2905     END IF;
2906 --
2907    RETURN l_balance;
2908 end calc_asg_td_ytd_date;
2909 --
2910 -----------------------------------------------------------------------------
2911 --added by skutteti
2912 -----------------------------------------------------------------------------
2913 --
2914 --                       CALC_ASG_TD_ODD_TWO_YTD_ACTION
2915 --
2916 --    This is the function for calculating assignment td two years to
2917 --                      date in asg action mode
2918 --
2919 -----------------------------------------------------------------------------
2920 --
2921 FUNCTION calc_asg_td_odd_two_ytd_action(
2922          p_assignment_action_id IN NUMBER,
2923          p_balance_type_id      IN NUMBER,
2924          p_effective_date       IN DATE DEFAULT NULL)
2925 RETURN NUMBER
2926 IS
2927 --
2928     l_assignment_action_id      NUMBER;
2929     l_balance                   NUMBER;
2930     l_assignment_id             NUMBER;
2931     l_effective_date            DATE;
2932 --
2933 BEGIN
2934 --
2935     l_assignment_id := get_correct_type(p_assignment_action_id);
2936     IF l_assignment_id is null THEN
2937 --
2938 --  The assignment action is not a payroll or quickpay type, so return null
2939 --
2940        l_balance := null;
2941     ELSE
2942 --
2943        l_balance := calc_asg_td_odd_two_ytd(
2944                              p_assignment_action_id => p_assignment_action_id,
2945                              p_balance_type_id      => p_balance_type_id,
2946                              p_effective_date       => p_effective_date,
2947                              p_assignment_id        => l_assignment_id);
2948     END IF;
2949 --
2950    RETURN l_balance;
2951 end calc_asg_td_odd_two_ytd_action;
2952 --
2953 -----------------------------------------------------------------------------
2954 --
2955 --                       CALC_ASG_TD_ODD_TWO_YTD_DATE
2956 --
2957 --    This is the function for calculating assignment two years to
2958 --                      date in date mode
2959 --
2960 -----------------------------------------------------------------------------
2961 --
2962 FUNCTION calc_asg_td_odd_two_ytd_date(
2963          p_assignment_id        IN NUMBER,
2964          p_balance_type_id      IN NUMBER,
2965          p_effective_date       IN DATE)
2966 RETURN NUMBER
2967 IS
2968 --
2969     l_assignment_action_id      NUMBER;
2970     l_balance                   NUMBER;
2971     l_end_date                  DATE;
2972     l_action_eff_date           DATE;
2973 --
2974 BEGIN
2975    --
2976    l_assignment_action_id := get_latest_action_id(p_assignment_id,
2977                                                   p_effective_date);
2978    IF l_assignment_action_id is null THEN
2979       l_balance := 0;
2980    ELSE
2981    --     start expiry chk now
2982       l_action_eff_date := get_latest_date(l_assignment_action_id);
2983    --
2984    --     Is effective date (sess) later than the expiry of the
2985    --     financial year of the  effective date.
2986    --
2987       if p_effective_date >= get_expired_two_year_date(l_action_eff_date
2988                                                       ,'ODD') then
2989          l_balance := 0;
2990       else
2991       --
2992       l_balance := calc_asg_td_odd_two_ytd(
2993                              p_assignment_action_id => l_assignment_action_id,
2994                              p_balance_type_id      => p_balance_type_id,
2995                              p_effective_date       => p_effective_date,
2996                              p_assignment_id        => p_assignment_id);
2997       end if;
2998    END IF;
2999    --
3000    RETURN l_balance;
3001    --
3002 end calc_asg_td_odd_two_ytd_date;
3003 --
3004 ------------------------------------------------------------------------------
3005 --
3006 --                      CALC_ASG_TD_ODD_TWO_YTD
3007 --      This function is for assignment tax district two years to date
3008 --      Calls Core balance package
3009 ------------------------------------------------------------------------------
3010 --
3011 FUNCTION calc_asg_td_odd_two_ytd(
3012         p_assignment_action_id  IN NUMBER,
3013         p_balance_type_id       IN NUMBER,
3014         p_effective_date        IN DATE DEFAULT NULL,
3015         p_assignment_id         IN NUMBER
3016                      )
3017 RETURN NUMBER
3018 IS
3019 --
3020         l_balance               NUMBER;
3021         l_defined_bal_id        NUMBER;
3022 --
3023    BEGIN
3024 --
3025 --Do we need to work out a value for this dimension/balance combination.
3026 --
3027  l_defined_bal_id := dimension_relevant(p_balance_type_id,
3028                                         '_ASG_TD_ODD_TWO_YTD');
3029  if l_defined_bal_id is not null then
3030    --
3031    -- Call core balance pkg with the defined balance just retrieved.
3032    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
3033                                           p_assignment_action_id);
3034    --
3035  else l_balance := null;
3036  end if;
3037 --
3038 RETURN l_balance;
3039 --
3040 END calc_asg_td_odd_two_ytd;
3041 -------------------------------------------------------------------------------
3042 --
3043 --                       CALC_ASG_TD_EVEN_TWO_YTD_ACTION
3044 --
3045 --    This is the function for calculating assignment td two years to
3046 --                      date in asg action mode
3047 --
3048 -----------------------------------------------------------------------------
3049 --
3050 FUNCTION calc_asg_td_even_two_ytd_actio(
3051          p_assignment_action_id IN NUMBER,
3052          p_balance_type_id      IN NUMBER,
3053          p_effective_date       IN DATE DEFAULT NULL)
3054 RETURN NUMBER
3055 IS
3056 --
3057     l_assignment_action_id      NUMBER;
3058     l_balance                   NUMBER;
3059     l_assignment_id             NUMBER;
3060     l_effective_date            DATE;
3061 --
3062 BEGIN
3063 --
3064     l_assignment_id := get_correct_type(p_assignment_action_id);
3065     IF l_assignment_id is null THEN
3066 --
3067 --  The assignment action is not a payroll or quickpay type, so return null
3068 --
3069        l_balance := null;
3070     ELSE
3071 --
3072        l_balance := calc_asg_td_even_two_ytd(
3073                                  p_assignment_action_id => p_assignment_action_id,
3074                                  p_balance_type_id      => p_balance_type_id,
3075                                  p_effective_date       => p_effective_date,
3076                                  p_assignment_id        => l_assignment_id);
3077     END IF;
3078 --
3079    RETURN l_balance;
3080 end calc_asg_td_even_two_ytd_actio;
3081 --
3082 -----------------------------------------------------------------------------
3083 --
3084 --                       CALC_ASG_TD_EVEN_TWO_YTD_DATE
3085 --
3086 --    This is the function for calculating assignment two years to
3087 --                      date in date mode
3088 -----------------------------------------------------------------------------
3089 --
3090 FUNCTION calc_asg_td_even_two_ytd_date(
3091          p_assignment_id        IN NUMBER,
3092          p_balance_type_id      IN NUMBER,
3093          p_effective_date       IN DATE)
3094 RETURN NUMBER
3095 IS
3096 --
3097     l_assignment_action_id      NUMBER;
3098     l_balance                   NUMBER;
3099     l_end_date                  DATE;
3100     l_action_eff_date           DATE;
3101 --
3102 BEGIN
3103 --
3104    l_assignment_action_id := get_latest_action_id(p_assignment_id,
3105                                                   p_effective_date);
3106    IF l_assignment_action_id is null THEN
3107       l_balance := 0;
3108    ELSE
3109       --     start expiry chk now
3110       l_action_eff_date := get_latest_date(l_assignment_action_id);
3111       --
3112       --   Is effective date (sess) later than the expiry of the
3113       --   financial year of the effective date.
3114       --
3115       if p_effective_date >= get_expired_two_year_date(l_action_eff_date
3116                                                       ,'EVEN')  then
3117          l_balance := 0;
3118       else
3119          --
3120          l_balance := calc_asg_td_even_two_ytd(
3121                              p_assignment_action_id => l_assignment_action_id,
3122                              p_balance_type_id      => p_balance_type_id,
3123                              p_effective_date       => p_effective_date,
3124                              p_assignment_id        => p_assignment_id);
3125       end if;
3126    END IF;
3127    --
3128    RETURN l_balance;
3129 end calc_asg_td_even_two_ytd_date;
3130 --
3131 ------------------------------------------------------------------------------
3132 --
3133 --                      CALC_ASG_TD_EVEN_TWO_YTD
3134 --      This function is for assignment tax district two years to date
3135 ------------------------------------------------------------------------------
3136 --
3137 FUNCTION calc_asg_td_even_two_ytd(
3138         p_assignment_action_id  IN NUMBER,
3139         p_balance_type_id       IN NUMBER,
3140         p_effective_date        IN DATE DEFAULT NULL,
3141         p_assignment_id         IN NUMBER
3142                      )
3143 RETURN NUMBER
3144 IS
3145 --
3146         l_balance               NUMBER;
3147         l_defined_bal_id        NUMBER;
3148 --
3149    BEGIN
3150 --
3151 --Do we need to work out a value for this dimension/balance combination.
3152 --
3153  l_defined_bal_id := dimension_relevant(p_balance_type_id,
3154                                         '_ASG_TD_EVEN_TWO_YTD');
3155  if l_defined_bal_id is not null then
3156    --
3157    -- Call core balance pkg with the defined balance just retrieved.
3158    l_balance := pay_balance_pkg.get_value(l_defined_bal_id,
3159                                           p_assignment_action_id);
3160    --
3161  else l_balance := null;
3162  end if;
3163 --
3164 RETURN l_balance;
3165 --
3166 END calc_asg_td_even_two_ytd;
3167 ----------------------------------------------------------------------------------
3168 --
3169 --                          CALC_BALANCE                                   --
3170 --  General function for accumulating a balance between two dates
3171 --
3172 --------------------------------------------------------------------------------
3173 
3174 FUNCTION calc_balance(
3175   p_assignment_id   IN NUMBER,
3176   p_balance_type_id IN NUMBER,  -- balance
3177   p_period_from_date  IN DATE,    -- since regular pay date of period
3178   p_event_from_date IN DATE,    -- since effective date of
3179   p_to_date   IN DATE,    -- sum up to this date
3180   p_action_sequence IN NUMBER)  -- sum up to this sequence
3181 RETURN NUMBER
3182 IS
3183 --
3184 --
3185   l_balance NUMBER;
3186 --
3187 BEGIN
3188 --
3189         SELECT  /*+ ORDERED INDEX (ASSACT PAY_ASSIGNMENT_ACTIONS_N51,
3190                                    PACT   PAY_PAYROLL_ACTIONS_PK,
3191                                    FEED   PAY_BALANCE_FEEDS_F_UK2,
3192                                    PPTP   PER_TIME_PERIODS_PK,
3193                                    RR     PAY_RUN_RESULTS_N50,
3194                                    TARGET PAY_RUN_RESULT_VALUES_PK) */
3195                 NVL(SUM(fnd_number.canonical_to_number(TARGET.result_value) * FEED.scale),0)
3196         INTO
3197                 l_balance
3198         FROM
3199                  pay_assignment_actions         ASSACT
3200                 ,pay_payroll_actions            PACT
3201                 ,pay_balance_feeds_f            FEED
3202                 ,per_time_periods               PPTP
3203                 ,pay_run_results                RR
3204                 ,pay_run_result_values          TARGET
3205         WHERE
3206                 FEED.balance_type_id = P_BALANCE_TYPE_ID
3207         AND     FEED.input_value_id = TARGET.input_value_id
3208         AND     TARGET.run_result_id = RR.run_result_id
3209         AND     RR.assignment_action_id = ASSACT.assignment_action_id
3210         AND     ASSACT.payroll_action_id = PACT.payroll_action_id
3211         AND     nvl(TARGET.result_value,'0') <> '0'
3212         AND     PACT.effective_date BETWEEN
3213                       FEED.effective_start_date AND FEED.effective_end_date
3214         AND     RR.status IN ('P','PA')
3215         AND     PACT.time_period_id = PPTP.time_period_id
3216         AND     PPTP.regular_payment_date >= P_PERIOD_FROM_DATE
3217         AND     PACT.effective_date >= P_EVENT_FROM_DATE
3218         AND     PACT.effective_date <= P_TO_DATE
3219         AND     ASSACT.action_sequence <= NVL(P_ACTION_SEQUENCE,ASSACT.action_sequence)
3220         AND     ASSACT.assignment_id = P_ASSIGNMENT_ID;
3221 
3222   RETURN l_balance;
3223 --
3224 END calc_balance;
3225 --
3226 
3227 --------------------------------------------------------------------------------
3228 --                                                                            --
3229 --                          CREATE DIMENSION                                  --
3230 --                                                                            --
3231 --------------------------------------------------------------------------------
3232 
3233 PROCEDURE create_dimension(
3234     errbuf     OUT NOCOPY VARCHAR2,
3235     retcode    OUT NOCOPY NUMBER,
3236     p_business_group_id IN  NUMBER,
3237     p_suffix    IN  VARCHAR2,
3238     p_level     IN  VARCHAR2,
3239     p_start_dd_mm   IN  VARCHAR2,
3240     p_frequency   IN  NUMBER,
3241     p_global_name   IN  VARCHAR2 DEFAULT NULL)
3242 IS
3243 BEGIN
3244   errbuf := NULL;
3245   retcode := 0;
3246 
3247 -- Bug Fix 12355069
3248 -- Test if online patching is in progress, if so, block execution
3249 --
3250 if ad_zd.get_edition('PATCH') is not null then
3251   -- an online patch is in progress, return error
3252   fnd_message.set_name('FND', 'AD_ZD_DISABLED_FEATURE');
3253   raise_application_error ('-20000', fnd_message.get);
3254 end if;
3255 
3256 ---------------------------
3257 -- INSERT INTO FF_ROUTES --
3258 ---------------------------
3259   DECLARE
3260     l_route_text  ff_routes.text%TYPE;
3261     l_bal_next    number;
3262   BEGIN
3263     SELECT
3264       pay_balance_dimensions_s.NEXTVAL
3265     INTO
3266       l_bal_next
3267     FROM DUAL;
3268 
3269     l_route_text :=
3270         'pay_gb_balances_v TARGET,
3271         pay_dummy_feeds_v FEED
3272         WHERE
3273           TARGET.assignment_action_id = &B1
3274         AND TARGET.balance_type_id = &U1
3275         AND TARGET.balance_dimension_id = ' || TO_CHAR(l_bal_next);
3276 --
3277 --
3278 
3279     INSERT INTO FF_ROUTES
3280     (
3281       route_id,
3282       route_name,
3283       user_defined_flag,
3284       description,
3285       text
3286     )
3287     VALUES
3288     (
3289       ff_routes_s.NEXTVAL,
3290       'ROUTE_NAME_' || ff_routes_s.CURRVAL ,
3291       'N',
3292       'User balance dimension for '||
3293                          UPPER(RPAD(p_suffix,30,' ')) || 'USER-REG ASG '||
3294                          p_start_dd_mm || ' RESET'|| TO_CHAR(p_frequency,'00'),
3295       l_route_text
3296     );
3297   END;
3298 
3299 -----------------------------------------
3300 -- INSERT INTO FF_ROUTE_CONTEXT_USAGES --
3301 -----------------------------------------
3302 
3303   BEGIN
3304     INSERT INTO ff_route_context_usages
3305     (
3306       route_id,
3307       context_id,
3308       sequence_no
3309     )
3310     SELECT
3311       ff_routes_s.CURRVAL,
3312       context_id,
3313       1
3314     FROM
3315       ff_contexts
3316     WHERE
3317       context_name = 'ASSIGNMENT_ACTION_ID';
3318   END;
3319 
3320 ------------------------------------
3321 -- INSERT INTO FF_ROUTE_PARAMETER --
3322 ------------------------------------
3323 
3324   BEGIN
3325     INSERT INTO ff_route_parameters
3326     (
3327       route_parameter_id,
3328       route_id,
3329       sequence_no,
3330       parameter_name,
3331       data_type
3332     )
3333     VALUES
3334     (
3335       ff_route_parameters_s.NEXTVAL,
3336       ff_routes_s.CURRVAL,
3337       1,
3338       'BALANCE TYPE ID',
3339       'N'
3340     );
3341   END;
3342 
3343 -----------------------------
3344 -- CREATION DIMENSION NAME --
3345 -----------------------------
3346 
3347   DECLARE
3348     l_dim_name  VARCHAR2(256);
3349     l_dim_type  VARCHAR2(1);
3350     l_dim_level VARCHAR2(3);
3351     l_req_id  NUMBER;
3352 
3353   BEGIN
3354 
3355     -- fill the dimension type
3356     IF p_level = 'ASSIGNMENT' THEN
3357       l_dim_type := 'A';
3358       l_dim_level := 'ASG';
3359     ELSIF p_level = 'PERSON' THEN
3360       l_dim_type := 'P';
3361       l_dim_level := 'PER';
3362     ELSIF p_level = 'ELEMENT' THEN
3363       l_dim_type := 'P';
3364       l_dim_level := 'ELE';
3365     ELSE
3366       l_dim_type := 'P';
3367       l_dim_level := 'PER';
3368     END IF;
3369 
3370 
3371     -- Fill the dimension name
3372     IF p_global_name IS NULL THEN
3373       -- USER REGULAR
3374                         l_dim_name := UPPER(RPAD(p_suffix,30,' ')) || 'USER-REG ';
3375       l_dim_name := l_dim_name || l_dim_level || ' ' ;
3376       l_dim_name := l_dim_name || p_start_dd_mm || ' RESET';
3377       l_dim_name := l_dim_name || TO_CHAR(p_frequency,'00');
3378     ELSE
3379       -- USER IRREGULAR
3380       /****************************/
3381       /*   Not yet implemented    */
3382       /****************************/
3383       /*
3384       l_dim_name := 'USER IRREGULAR DIMENSION FOR ';
3385       l_dim_name := l_dim_name || p_level || ' BASED ON ' || p_global_name;
3386       */
3387       null;
3388     END IF;
3389 
3390     -- Find the current request id
3391     l_req_id := fnd_profile.value('CONC_REQUEST_ID');
3392 
3393     -- insert into the table
3394     INSERT INTO pay_balance_dimensions
3395     (
3396       balance_dimension_id,
3397       business_group_id,
3398       legislation_code,
3399       route_id,
3400       database_item_suffix,
3401       dimension_name,
3402       dimension_type,
3403       description,
3404       feed_checking_code,
3405       legislation_subgroup,
3406       payments_flag,
3407       expiry_checking_code,
3408       expiry_checking_level,
3409       feed_checking_type
3410     )
3411     VALUES
3412     (
3413       pay_balance_dimensions_s.CURRVAL,
3414       p_business_group_id,
3415       NULL,
3416       ff_routes_s.CURRVAL,
3417       p_suffix,
3418       l_dim_name,
3419       l_dim_type,
3420       'User dimension defined by Request Id ' || l_req_id,
3421       NULL,
3422       NULL,
3423       'N',
3424       'hr_gbbal.check_expiry',
3425       'P',
3426       NULL
3427     );
3428 
3429   END;
3430 END create_dimension;
3431 --------------------------------------------------------------------------------
3432 --                                                                            --
3433 --                          EXPIRY CHECKING CODE                    --
3434 --                                                                            --
3435 --------------------------------------------------------------------------------
3436 PROCEDURE check_expiry(
3437     p_owner_payroll_action_id   IN  NUMBER,
3438     p_user_payroll_action_id    IN  NUMBER,
3439     p_owner_assignment_action_id    IN  NUMBER,
3440     p_user_assignment_action_id   IN  NUMBER,
3441     p_owner_effective_date      IN  DATE,
3442     p_user_effective_date     IN  DATE,
3443     p_dimension_name      IN  VARCHAR2,
3444     p_expiry_information     OUT NOCOPY NUMBER)
3445 IS
3446     p_user_start_period DATE;
3447     p_owner_start_period  DATE;
3448 BEGIN
3449 
3450   -- This is only for USER REGULAR BALANCES
3451   p_user_start_period  := hr_gbbal.dimension_reset_date(p_dimension_name, p_user_effective_date,null);
3452   p_owner_start_period := hr_gbbal.dimension_reset_date(p_dimension_name, p_owner_effective_date,null);
3453   IF p_user_start_period = p_owner_start_period THEN
3454     p_expiry_information := 0; -- FALSE
3455   ELSE
3456     p_expiry_information := 1; -- TRUE
3457   END IF;
3458 
3459 END check_expiry;
3460 --------------------------------------------------------------------------------
3461 --                          EXPIRY CHECKING CODE  For Prevention              --
3462 --                          of loss of latest balance (for 115.63)
3463 --------------------------------------------------------------------------------
3464 
3465 PROCEDURE check_expiry(
3466     p_owner_payroll_action_id     IN  NUMBER,
3467     p_user_payroll_action_id      IN  NUMBER,
3468     p_owner_assignment_action_id  IN  NUMBER,
3469     p_user_assignment_action_id   IN  NUMBER,
3470     p_owner_effective_date        IN  DATE,
3471     p_user_effective_date         IN  DATE,
3472     p_dimension_name              IN  VARCHAR2,
3473     p_expiry_information         OUT NOCOPY DATE)
3474 
3475 IS
3476    p_owner_start_period  DATE;
3477    l_regular_payment_date DATE;
3478 
3479   l_start_dd_mon    VARCHAR2(7);
3480   l_frequency   NUMBER;
3481   l_start_reset   NUMBER;
3482 
3483 BEGIN
3484 
3485    SELECT PTP.regular_payment_date
3486      INTO l_regular_payment_date
3487      FROM per_time_periods    PTP,
3488           pay_payroll_actions BACT
3489     WHERE BACT.payroll_action_id = p_owner_payroll_action_id
3490       AND PTP.time_period_id = BACT.time_period_id;
3491 
3492 
3493    IF p_dimension_name = '_ASG_CALENDAR_QTD             USER-REG ASG 01-01 RESET 04'
3494    THEN
3495       p_expiry_information := TRUNC(ADD_MONTHS(l_regular_payment_date, 3), 'Q')-1;
3496 
3497    ELSIF p_dimension_name = '_ASG_QTD                      USER-REG ASG 06-04 RESET 04'
3498    THEN
3499       p_owner_start_period := hr_gbbal.dimension_reset_date(p_dimension_name, p_owner_effective_date,null);
3500 
3501       p_expiry_information := ADD_MONTHS(p_owner_start_period,3) - 1;
3502       -- TRUNC(ADD_MONTHS(p_owner_effective_date, 3), 'Q')+ 4;
3503 
3504    ELSIF p_dimension_name = '_ASG_CALENDAR_YTD             USER-REG ASG 01-01 RESET 01'
3505    THEN
3506       p_expiry_information := TRUNC(ADD_MONTHS(l_regular_payment_date, 12), 'Y')-1;
3507 
3508 /* Start of Bug Fix 10092794. Added the below else block to arrive at the Expiry date for User generated
3509    Regular Balance Dimensions. Code will pass on the user effective date to span_end procedure to
3510    identify the expiry date */
3511 
3512    ELSE
3513     IF SUBSTR(p_dimension_name,31,8) = 'USER-REG' THEN
3514       l_start_reset := INSTR(p_dimension_name,'RESET',30);
3515       l_start_dd_mon := SUBSTR(p_dimension_name, l_start_reset - 6, 5);
3516       l_frequency := FND_NUMBER.CANONICAL_TO_NUMBER(SUBSTR
3517                                        (p_dimension_name, l_start_reset + 6, 2));
3518 
3519       p_expiry_information := span_end(p_owner_effective_date,l_frequency, l_start_dd_mon);
3520     END IF;
3521 
3522 /* End of Bug Fix 10092794 */
3523    END IF;
3524 
3525 END check_expiry;
3526 
3527 -------------------------------------------------------------------------------
3528 --
3529 --     FUNCTION get_element_reference.
3530 --     This function returns an element balance reference number
3531 --     for identification purposes, which is suffixed by ITD or PTD
3532 --     depending on the balance, and used as the reported dimension name.
3533 --     Where there is no reference, the displayed dimension defaults to
3534 --     _ELEMENT_PTD or _ELEMENT_ITD.
3535 --     Bug 1146055, use Run Results instead of element entries,
3536 --     note still uses view pay_input_values.
3537 --
3538 -------------------------------------------------------------------------------
3539 --
3540 FUNCTION get_element_reference(p_run_result_id        IN NUMBER,
3541              p_database_item_suffix IN VARCHAR2)
3542 RETURN VARCHAR2 IS
3543 --
3544 l_reference varchar2(60);
3545 l_suffix varchar2(4);
3546 l_prefix varchar2(20);
3547 l_original_entry_id number;
3548 --
3549 cursor get_run_result_value (c_run_result_id  NUMBER) is
3550   SELECT prrv.result_value
3551   FROM   pay_run_result_values prrv,
3552          pay_run_results prr,
3553          pay_input_values iv
3554   WHERE  prr.run_result_id = c_run_result_id
3555   AND    prr.run_result_id = prrv.run_result_id
3556   AND    iv.name  = 'Reference'
3557   AND    iv.input_value_id = prrv.input_value_id;
3558 
3559 cursor get_source_id(c_run_result_id NUMBER) IS
3560   SELECT prr.source_id
3561   FROM   pay_run_results prr
3562   WHERE  prr.run_result_id = c_run_result_id;
3563 
3564 --
3565 BEGIN
3566 --
3567   open get_run_result_value (p_run_result_id);
3568   fetch get_run_result_value into l_reference;
3569   close get_run_result_value;
3570 
3571   open  get_source_id (p_run_result_id);
3572   fetch get_source_id into l_original_entry_id;
3573   close get_source_id;
3574 --
3575   /*For bug fix 4452262*/
3576   if p_database_item_suffix in ('_ELEMENT_ITD','_ELEMENT_PTD') then
3577 
3578       l_prefix := substr(p_database_item_suffix,1, length(p_database_item_suffix)-3);
3579       l_suffix := substr(p_database_item_suffix, -4);
3580       l_reference := l_prefix|| l_original_entry_id || l_suffix;
3581 
3582   elsif  p_database_item_suffix in ('_ELEMENT_CO_REF_ITD') then
3583 
3584       l_prefix := substr(p_database_item_suffix,1, length(p_database_item_suffix)-3);
3585       l_suffix := substr(p_database_item_suffix, -4);
3586       l_reference := l_prefix|| l_reference || l_suffix;
3587 
3588   elsif (l_reference is null or l_reference = 'Unknown') then
3589       l_reference := p_database_item_suffix;
3590 
3591   else
3592       l_reference := p_database_item_suffix;
3593   end if;
3594 --
3595 RETURN l_reference;
3596 END get_element_reference;
3597 
3598 -------------------------------------------------------------------------------
3599 --
3600 --     FUNCTION get_context_references.
3601 --     This function returns context value,  which is suffixed by ITD or PTD
3602 --     depending on the balance, and used as the reported dimension name.
3603 --     Where there is no context value, the displayed dimension defaults to
3604 --     database item suffix.
3605 --
3606 -------------------------------------------------------------------------------
3607 
3608 FUNCTION get_context_references(p_context_value        IN VARCHAR2,
3609               p_database_item_suffix IN VARCHAR2)
3610 RETURN VARCHAR2 IS
3611 --
3612 l_context varchar2(60);
3613 l_suffix varchar2(4);
3614 l_prefix varchar2(15);
3615 --
3616 BEGIN
3617 
3618    if p_context_value is null or  p_context_value = 'Unknown' then
3619       l_context := p_database_item_suffix;
3620    else
3621           l_context := p_database_item_suffix;
3622           l_suffix := substr(p_database_item_suffix, -4);
3623           l_prefix := substr(p_database_item_suffix,1,11);
3624           l_context := l_prefix || p_context_value || l_suffix;
3625 
3626    end if;
3627 --
3628 RETURN l_context;
3629 END get_context_references;
3630 
3631 -----------------------------------------------------------------------
3632 function ni_category_exists_in_year (p_assignment_action_id in number,
3633                                      p_category in varchar2)
3634 RETURN number is
3635    l_return number;
3636    l_regular_payment_date per_time_periods.regular_payment_date%type;
3637    l_niable_def_id pay_defined_balances.defined_balance_id%type;
3638    l_nitotal_def_id pay_defined_balances.defined_balance_id%type;
3639    l_nitotal_value number;
3640    l_niable_value number;
3641 --
3642 
3643 /*Added for bug fix 4088228, to get the child assignment_action_id*/
3644 
3645 cursor csr_child_asg_actid
3646 is
3647     SELECT max(paa.assignment_action_id)
3648     FROM pay_assignment_actions paa
3649     WHERE
3650          paa.source_action_id = p_assignment_action_id
3651     AND  paa.source_action_id is not null;
3652 
3653 cursor csr_latest_bal (c_asg_action_id IN NUMBER,
3654            c_defined_balance_id IN NUMBER) is
3655         SELECT value
3656         from pay_assignment_latest_balances
3657         Where assignment_action_id = c_asg_action_id
3658         and   defined_balance_id = c_defined_balance_id;
3659 
3660 cursor CSR_ni_entries is
3661 select distinct pel.element_type_id element_type_id,
3662     nvl(ent.original_entry_id, ent.element_entry_id) source_id
3663        from pay_element_entries_f ent,
3664       pay_element_links_f pel,
3665       pay_user_rows_f urows,
3666       pay_payroll_actions bact,
3667       per_time_periods bptp,
3668       pay_assignment_actions bassact
3669         where bassact.assignment_action_id = p_assignment_action_id
3670   and   UROWS.user_table_id = g_ni_cat_indicator_table_id
3671         and   fnd_number.canonical_to_number(UROWS.ROW_LOW_RANGE_OR_NAME)  = PEL.ELEMENT_TYPE_ID
3672   and   g_start_of_year between
3673         UROWS.effective_start_date and UROWS.effective_end_date
3674   and   bact.payroll_action_id = bassact.payroll_action_id
3675   and   bptp.time_period_id = bact.time_period_id
3676   and   ent.assignment_id = bassact.assignment_id
3677         and  ent.effective_end_date >= g_start_of_year
3678   and  ent.effective_start_date <= bptp.end_date
3679   and  ent.element_link_id = pel.element_link_id
3680   and  pel.business_group_id + 0 = bact.business_group_id
3681   and ent.effective_end_date between
3682     pel.effective_start_date and pel.effective_end_date;
3683 
3684 cursor CSR_ni_run_results_exist (p_source_id number) is
3685 select    max(decode(PRR.element_type_id,g_ni_a_element_type_id,1,0))
3686         , max(decode(PRR.element_type_id,g_ni_b_element_type_id,1,0))
3687         , max(decode(PRR.element_type_id,g_ni_c_element_type_id,1,0))
3688         , max(decode(PRR.element_type_id,g_ni_d_element_type_id,1,0))
3689         , max(decode(PRR.element_type_id,g_ni_e_element_type_id,1,0))
3690         , max(decode(PRR.element_type_id,g_ni_f_element_type_id,1,0))
3691         , max(decode(PRR.element_type_id,g_ni_g_element_type_id,1,0))
3692         , max(decode(PRR.element_type_id,g_ni_j_element_type_id,1,0))
3693         , max(decode(PRR.element_type_id,g_ni_l_element_type_id,1,0))
3694         , max(decode(PRR.element_type_id,g_ni_s_element_type_id,1,0))
3695 from
3696                 PAY_RUN_RESULTS        PRR
3697          ,      PER_TIME_PERIODS       PPTP
3698          ,      PAY_PAYROLL_ACTIONS    PACT
3699          ,      PAY_ASSIGNMENT_ACTIONS ASSACT
3700          ,      PAY_ASSIGNMENT_ACTIONS BASSACT
3701          where  PRR.source_id = p_source_id
3702          and    PRR.source_type = 'I'
3703          AND    PACT.PAYROLL_ACTION_ID   = ASSACT.PAYROLL_ACTION_ID
3704    AND    PACT.ACTION_TYPE <> 'I'
3705          AND    PPTP.TIME_PERIOD_ID      = PACT.TIME_PERIOD_ID
3706          AND    PPTP.regular_payment_date >= g_start_of_year
3707          AND    BASSACT.ASSIGNMENT_ACTION_ID = p_assignment_action_id
3708          AND    ASSACT.ACTION_SEQUENCE <= BASSACT.ACTION_SEQUENCE
3709          AND    ASSACT.ASSIGNMENT_ACTION_ID  = PRR.ASSIGNMENT_ACTION_ID
3710          AND    ASSACT.ASSIGNMENT_ID       = BASSACT.ASSIGNMENT_ID;
3711 
3712 cursor CSR_run_results_exist is
3713 select    max(decode(FEED.balance_type_id,g_ni_a_id,1,g_ni_a_able_id,1,0))
3714         , max(decode(FEED.balance_type_id,g_ni_b_id,1,g_ni_b_able_id,1,0))
3715         , max(decode(FEED.balance_type_id,g_ni_c_id,1,g_ni_c_able_id,1,0))
3716         , max(decode(FEED.balance_type_id,g_ni_d_id,1,g_ni_d_able_id,1,0))
3717         , max(decode(FEED.balance_type_id,g_ni_e_id,1,g_ni_e_able_id,1,0))
3718         , max(decode(FEED.balance_type_id,g_ni_f_id,1,g_ni_f_able_id,1,0))
3719         , max(decode(FEED.balance_type_id,g_ni_g_id,1,g_ni_g_able_id,1,0))
3720         , max(decode(FEED.balance_type_id,g_ni_j_id,1,g_ni_j_able_id,1,0))
3721         , max(decode(FEED.balance_type_id,g_ni_l_id,1,g_ni_l_able_id,1,0))
3722         , max(decode(FEED.balance_type_id,g_ni_s_id,1,g_ni_s_able_id,1,0))
3723 from
3724     PAY_BALANCE_FEEDS_F    FEED
3725          ,      PAY_RUN_RESULT_VALUES  PRRV
3726          ,      PAY_RUN_RESULTS        PRR
3727          ,      PER_TIME_PERIODS       PPTP
3728          ,      PAY_PAYROLL_ACTIONS    PACT
3729          ,      PAY_ASSIGNMENT_ACTIONS ASSACT
3730          ,      PAY_ASSIGNMENT_ACTIONS BASSACT
3731    WHERE   FEED.balance_type_id in (
3732      g_ni_a_id, g_ni_a_able_id
3733     ,g_ni_b_id, g_ni_b_able_id
3734     ,g_ni_c_id, g_ni_c_able_id
3735     ,g_ni_d_id, g_ni_d_able_id
3736     ,g_ni_e_id, g_ni_e_able_id
3737     ,g_ni_f_id, g_ni_f_able_id
3738     ,g_ni_g_id, g_ni_g_able_id
3739     ,g_ni_j_id, g_ni_j_able_id
3740     ,g_ni_l_id, g_ni_l_able_id
3741     ,g_ni_s_id, g_ni_s_able_id
3742     )
3743          AND    PRR.RUN_RESULT_ID       = PRRV.RUN_RESULT_ID
3744          AND    PACT.PAYROLL_ACTION_ID   = ASSACT.PAYROLL_ACTION_ID
3745    AND    PACT.action_type in ('I',g_action_typer,g_action_typeq,g_action_typeb)
3746          AND    PPTP.TIME_PERIOD_ID      = PACT.TIME_PERIOD_ID
3747          AND    PPTP.regular_payment_date >= g_start_of_year
3748          AND    BASSACT.ASSIGNMENT_ACTION_ID = p_assignment_action_id
3749          AND    PRRV.RESULT_VALUE IS NOT NULL
3750          AND    PRRV.RESULT_VALUE <> '0'
3751          AND    PPTP.regular_payment_date is not null
3752    AND    FEED.INPUT_VALUE_ID = PRRV.INPUT_VALUE_ID
3753    AND    PACT.effective_date between
3754         FEED.effective_start_date and FEED.effective_end_date
3755          AND    ASSACT.ACTION_SEQUENCE <= BASSACT.ACTION_SEQUENCE
3756          AND    ASSACT.ASSIGNMENT_ACTION_ID = PRR.ASSIGNMENT_ACTION_ID
3757          AND    ASSACT.ASSIGNMENT_ID       = BASSACT.ASSIGNMENT_ID;
3758 --BUG Changed cursor for improving performance 3221422
3759 --Remove this cursor for bug 4120063
3760 /*
3761 cursor CSR_initialization_exists is
3762 select   1
3763 from per_time_periods ptp
3764 where ptp.regular_payment_date >= g_start_of_year
3765 and ptp.time_period_id in
3766     (
3767     select
3768     null
3769     from pay_payroll_actions pact
3770     where pact.action_type = 'I'
3771     );
3772 */
3773 --
3774 cursor csr_asg_action_info (c_assignment_action_id IN NUMBER) IS
3775    select paa.assignment_id,
3776           paa.action_sequence,
3777           ppa.effective_date
3778    from pay_assignment_actions paa,
3779         pay_payroll_actions ppa
3780    where paa.assignment_action_id = c_assignment_action_id
3781    and   paa.payroll_action_id = ppa.payroll_action_id;
3782 --
3783 l_ni_a_exists_adj number;
3784 l_ni_b_exists_adj number;
3785 l_ni_c_exists_adj number;
3786 l_ni_d_exists_adj number;
3787 l_ni_e_exists_adj number;
3788 l_ni_f_exists_adj number;
3789 l_ni_g_exists_adj number;
3790 l_ni_j_exists_adj number;
3791 l_ni_l_exists_adj number;
3792 l_ni_s_exists_adj number;
3793 
3794 /*Added for bug fix 4088228*/
3795 v_assignment_action_id  pay_assignment_actions.assignment_action_id%TYPE;
3796 p_assignment_action_id_child pay_assignment_actions.assignment_action_id%TYPE;
3797 v_master_exist  varchar2(1);
3798 
3799 begin
3800 --
3801 
3802  /*Added for bug fix 4088228*/
3803 
3804   open csr_child_asg_actid;
3805   fetch csr_child_asg_actid into v_assignment_action_id;
3806   close csr_child_asg_actid;
3807 
3808 if v_assignment_action_id is not null then
3809     p_assignment_action_id_child := v_assignment_action_id;
3810 else
3811     p_assignment_action_id_child := p_assignment_action_id;
3812 end if;
3813 
3814 if p_assignment_action_id_child is null or p_category is null then --Bug fix 4099228
3815   return null;
3816 end if;
3817 --
3818 if g_ni_a_id is null then -- first call this session
3819         begin
3820                 select user_table_id
3821                 into g_ni_cat_indicator_table_id
3822                         from pay_user_tables
3823                 where user_table_name = 'NI_CATEGORY_INDICATOR_ELEMENTS'
3824                 and legislation_code = 'GB';
3825        -- if not found raise error
3826        EXCEPTION WHEN no_data_found THEN
3827           g_action_typer := 'R';
3828           g_action_typeq := 'Q';
3829           g_action_typeb := 'B';
3830         end;
3831 
3832        end if;
3833 
3834 if g_ni_a_id is null then -- first call this session
3835 select   max(decode(balance_name, 'NI A Total',balance_type_id,0))
3836         ,max(decode(balance_name, 'NI A Able' ,balance_type_id,0))
3837         ,max(decode(balance_name, 'NI B Total',balance_type_id,0))
3838         ,max(decode(balance_name, 'NI B Able' ,balance_type_id,0))
3839         ,max(decode(balance_name, 'NI C Total',balance_type_id,0))
3840         ,max(decode(balance_name, 'NI C Able' ,balance_type_id,0))
3841         ,max(decode(balance_name, 'NI D Total',balance_type_id,0))
3842         ,max(decode(balance_name, 'NI D Able' ,balance_type_id,0))
3843         ,max(decode(balance_name, 'NI E Total',balance_type_id,0))
3844         ,max(decode(balance_name, 'NI E Able' ,balance_type_id,0))
3845         ,max(decode(balance_name, 'NI F Total',balance_type_id,0))
3846         ,max(decode(balance_name, 'NI F Able' ,balance_type_id,0))
3847         ,max(decode(balance_name, 'NI G Total',balance_type_id,0))
3848         ,max(decode(balance_name, 'NI G Able' ,balance_type_id,0))
3849         ,max(decode(balance_name, 'NI J Total',balance_type_id,0))
3850         ,max(decode(balance_name, 'NI J Able' ,balance_type_id,0))
3851         ,max(decode(balance_name, 'NI L Total',balance_type_id,0))
3852         ,max(decode(balance_name, 'NI L Able' ,balance_type_id,0))
3853         ,max(decode(balance_name, 'NI S Total',balance_type_id,0))
3854         ,max(decode(balance_name, 'NI S Able' ,balance_type_id,0))
3855         into
3856          g_ni_a_id, g_ni_a_able_id
3857         ,g_ni_b_id, g_ni_b_able_id
3858         ,g_ni_c_id, g_ni_c_able_id
3859         ,g_ni_d_id, g_ni_d_able_id
3860         ,g_ni_e_id, g_ni_e_able_id
3861         ,g_ni_f_id, g_ni_f_able_id
3862         ,g_ni_g_id, g_ni_g_able_id
3863         ,g_ni_j_id, g_ni_j_able_id
3864         ,g_ni_l_id, g_ni_l_able_id
3865         ,g_ni_s_id, g_ni_s_able_id
3866         from pay_balance_types
3867         where balance_name in (
3868          'NI A Total', 'NI A Able'
3869         ,'NI B Total', 'NI B Able'
3870         ,'NI C Total', 'NI C Able'
3871         ,'NI D Total', 'NI D Able'
3872         ,'NI E Total', 'NI E Able'
3873         ,'NI F Total', 'NI F Able'
3874         ,'NI G Total', 'NI G Able'
3875         ,'NI J Total', 'NI J Able'
3876         ,'NI L Total', 'NI L Able'
3877         ,'NI S Total', 'NI S Able'
3878         )
3879         and legislation_code = 'GB';
3880 end if;
3881 --
3882 if g_ni_element_type_id is null then -- first call this session
3883         select
3884         max(ptp.regular_payment_date)
3885         ,max(decode(e.element_name,'NI',e.element_type_id,0))
3886         ,max(decode(e.element_name,'NI A',e.element_type_id,0))
3887         ,max(decode(e.element_name,'NI B',e.element_type_id,0))
3888         ,max(decode(e.element_name,'NI C',e.element_type_id,0))
3889         ,max(decode(e.element_name,'NI D',e.element_type_id,0))
3890         ,max(decode(e.element_name,'NI E',e.element_type_id,0))
3891         ,max(decode(e.element_name,'NI F',e.element_type_id,0))
3892         ,max(decode(e.element_name,'NI G',e.element_type_id,0))
3893         ,max(decode(e.element_name,'NI J Deferment',e.element_type_id,0))
3894         ,max(decode(e.element_name,'NI L Deferment',e.element_type_id,0))
3895         ,max(decode(e.element_name,'NI S',e.element_type_id,0))
3896              into
3897              l_regular_payment_date
3898              ,g_ni_element_type_id
3899              ,g_ni_a_element_type_id
3900              ,g_ni_b_element_type_id
3901              ,g_ni_c_element_type_id
3902              ,g_ni_d_element_type_id
3903              ,g_ni_e_element_type_id
3904              ,g_ni_f_element_type_id
3905              ,g_ni_g_element_type_id
3906              ,g_ni_j_element_type_id
3907              ,g_ni_l_element_type_id
3908              ,g_ni_s_element_type_id
3909              from pay_element_types_f e,
3910                   per_time_periods ptp,
3911                   pay_payroll_actions bact,
3912                   pay_assignment_actions bassact
3913              where element_name in (     'NI'
3914                                         ,'NI A'
3915                                         ,'NI B'
3916                                         ,'NI C'
3917                                         ,'NI D'
3918                                         ,'NI E'
3919                                         ,'NI F'
3920                                         ,'NI G'
3921                                         ,'NI J Deferment'
3922                                         ,'NI L Deferment'
3923                                         ,'NI S')
3924                and e.legislation_code = 'GB'
3925                and bassact.assignment_action_id = p_assignment_action_id_child -- bug fix 4088228
3926                and bassact.payroll_action_id = bact.payroll_action_id
3927                and ptp.time_period_id = bact.time_period_id
3928                and bact.date_earned between
3929                     e.effective_start_date and e.effective_end_date;
3930 end if;
3931 --
3932    -- first time through check whether any balance initializations have happened
3933    -- in the tax year - if not we don't need to check the initialization on
3934    -- individual balances.
3935 
3936 
3937 
3938    begin
3939     if g_start_of_year is null then -- first call this session
3940        g_start_of_year := hr_gbbal.span_start(l_regular_payment_date, 1, '06-04');
3941        /*
3942        open  CSR_initialization_exists;
3943        fetch CSR_initialization_exists into g_initialization_exists;
3944        close CSR_initialization_exists;
3945        */
3946     end if;
3947    end;
3948    --
3949    -- setup balance dimension id
3950    --
3951    if g_asg_td_ytd is null then
3952       select balance_dimension_id
3953       into g_asg_td_ytd
3954       from pay_balance_dimensions
3955       where dimension_name = '_ASG_TD_YTD';
3956    end if;
3957    --
3958    -- Check to see whether there are any latest balances for the
3959    -- NI <CAT> Total or NI <CAT> Able balances, for the dimension
3960    -- _ASG_TD_YTD. If so, we do not need to loop through the
3961    -- run results below. Use already cached balance type id's.
3962    --
3963    IF g_ni_a_defbal_id is null then
3964     -- First call this session, set up defined balances.
3965     select max(decode(balance_type_id,g_ni_a_id,defined_balance_id,0))
3966           ,max(decode(balance_type_id,g_ni_a_able_id,defined_balance_id,0))
3967           ,max(decode(balance_type_id,g_ni_b_id,defined_balance_id,0))
3968           ,max(decode(balance_type_id,g_ni_b_able_id,defined_balance_id,0))
3969           ,max(decode(balance_type_id,g_ni_c_id,defined_balance_id,0))
3970           ,max(decode(balance_type_id,g_ni_c_able_id,defined_balance_id,0))
3971           ,max(decode(balance_type_id,g_ni_d_id,defined_balance_id,0))
3972           ,max(decode(balance_type_id,g_ni_d_able_id,defined_balance_id,0))
3973           ,max(decode(balance_type_id,g_ni_e_id,defined_balance_id,0))
3974           ,max(decode(balance_type_id,g_ni_e_able_id,defined_balance_id,0))
3975           ,max(decode(balance_type_id,g_ni_f_id,defined_balance_id,0))
3976           ,max(decode(balance_type_id,g_ni_f_able_id,defined_balance_id,0))
3977           ,max(decode(balance_type_id,g_ni_g_id,defined_balance_id,0))
3978           ,max(decode(balance_type_id,g_ni_g_able_id,defined_balance_id,0))
3979           ,max(decode(balance_type_id,g_ni_j_id,defined_balance_id,0))
3980           ,max(decode(balance_type_id,g_ni_j_able_id,defined_balance_id,0))
3981           ,max(decode(balance_type_id,g_ni_l_id,defined_balance_id,0))
3982           ,max(decode(balance_type_id,g_ni_l_able_id,defined_balance_id,0))
3983           ,max(decode(balance_type_id,g_ni_s_id,defined_balance_id,0))
3984           ,max(decode(balance_type_id,g_ni_s_able_id,defined_balance_id,0))
3985     into
3986       g_ni_a_defbal_id,
3987       g_ni_a_able_defbal_id,
3988       g_ni_b_defbal_id,
3989       g_ni_b_able_defbal_id,
3990       g_ni_c_defbal_id,
3991       g_ni_c_able_defbal_id,
3992       g_ni_d_defbal_id,
3993       g_ni_d_able_defbal_id,
3994       g_ni_e_defbal_id,
3995       g_ni_e_able_defbal_id,
3996       g_ni_f_defbal_id,
3997       g_ni_f_able_defbal_id,
3998       g_ni_g_defbal_id,
3999       g_ni_g_able_defbal_id,
4000       g_ni_j_defbal_id,
4001       g_ni_j_able_defbal_id,
4002       g_ni_l_defbal_id,
4003       g_ni_l_able_defbal_id,
4004       g_ni_s_defbal_id,
4005       g_ni_s_able_defbal_id
4006     from pay_defined_balances
4007     where balance_dimension_id = g_asg_td_ytd
4008     and balance_type_id in
4009      (g_ni_a_id, g_ni_a_able_id
4010         ,g_ni_b_id, g_ni_b_able_id
4011         ,g_ni_c_id, g_ni_c_able_id
4012         ,g_ni_d_id, g_ni_d_able_id
4013         ,g_ni_e_id, g_ni_e_able_id
4014         ,g_ni_f_id, g_ni_f_able_id
4015         ,g_ni_g_id, g_ni_g_able_id
4016         ,g_ni_j_id, g_ni_j_able_id
4017         ,g_ni_l_id, g_ni_l_able_id
4018         ,g_ni_s_id, g_ni_s_able_id)
4019     and legislation_code = 'GB'
4020     and business_group_id is null;
4021    --
4022    END IF; -- Setup cached defined balances
4023    --
4024    -- Choose the relevant defined balance for latest balance
4025    -- call according to category.
4026    --
4027    If p_category = 'A' then
4028       l_nitotal_def_id := g_ni_a_defbal_id;
4029       l_niable_def_id := g_ni_a_able_defbal_id;
4030    Elsif p_category = 'B' then
4031       l_nitotal_def_id := g_ni_b_defbal_id;
4032       l_niable_def_id := g_ni_b_able_defbal_id;
4033    Elsif p_category = 'C' then
4034       l_nitotal_def_id := g_ni_c_defbal_id;
4035       l_niable_def_id := g_ni_c_able_defbal_id;
4036    Elsif p_category = 'D' then
4037       l_nitotal_def_id := g_ni_d_defbal_id;
4038       l_niable_def_id := g_ni_d_able_defbal_id;
4039    Elsif p_category = 'E' then
4040       l_nitotal_def_id := g_ni_e_defbal_id;
4041       l_niable_def_id := g_ni_e_able_defbal_id;
4042    Elsif p_category = 'F' then
4043       l_nitotal_def_id := g_ni_f_defbal_id;
4044       l_niable_def_id := g_ni_f_able_defbal_id;
4045    Elsif p_category = 'G' then
4046       l_nitotal_def_id := g_ni_g_defbal_id;
4047       l_niable_def_id := g_ni_g_able_defbal_id;
4048    Elsif p_category = 'J' then
4049       l_nitotal_def_id := g_ni_j_defbal_id;
4050       l_niable_def_id := g_ni_j_able_defbal_id;
4051    Elsif p_category = 'L' then
4052       l_nitotal_def_id := g_ni_l_defbal_id;
4053       l_niable_def_id := g_ni_l_able_defbal_id;
4054    Elsif p_category = 'S' then
4055       l_nitotal_def_id := g_ni_s_defbal_id;
4056       l_niable_def_id := g_ni_s_able_defbal_id;
4057    End If;
4058    --
4059 
4060 
4061    if p_assignment_action_id_child <> nvl(g_assignment_action_id2, -1) then --bug fix 4088228
4062      --
4063      open csr_asg_action_info(p_assignment_action_id_child);  --bug fix 4088228
4064      fetch csr_asg_action_info into g_assignment_id,
4065                                     g_action_sequence,
4066                                     g_effective_date;
4067      close csr_asg_action_info;
4068      --
4069      g_assignment_action_id2 := p_assignment_action_id_child; -- bug fix 4088228
4070      --
4071    end if;
4072    --
4073    -- Check to see if any latest balances first.
4074    --
4075    l_nitotal_value := null;
4076    l_niable_value := null;
4077    --
4078    open csr_latest_bal(p_assignment_action_id_child, l_nitotal_def_id);  -- bug fix 4088228
4079    fetch csr_latest_bal into l_nitotal_value;
4080    close csr_latest_bal;
4081    --
4082    open csr_latest_bal(p_assignment_action_id_child, l_niable_def_id); --bug fix 4088228
4083    fetch csr_latest_bal into l_niable_value;
4084    close csr_latest_bal;
4085    --
4086    -- If either total or able latest balances are null, then the
4087    -- Run Results cursors are used.
4088    --
4089    IF l_nitotal_value is null OR l_niable_value is null THEN
4090       --
4091       -- if a non zero result exists for either the NI Cat Total or the
4092       -- NI Cat Niable balance within the year the category has existed
4093       -- Prior to April 00 NI Cat Total indicated a category was reported
4094       -- for the assignment.  However the introduction of the EET threshold
4095       -- and balances means that even without a deduction being taken
4096       -- EET balances, Able Balances and EES Rebate balances need to be
4097       -- reported.
4098       -- If NI Earnings are above the LEL than NI Cat Able is recorded up
4099       -- test NI Cat Total which will be non zero in this instance.
4100       -- first call for this assignment action
4101       if nvl(g_assignment_action_id,-1) <> p_assignment_action_id_child then --bug fix 4088228
4102 
4103          g_assignment_action_id := p_assignment_action_id_child; --bug fix 4088228
4104        -- first check for the normal run indirects in the year
4105        -- The normal way for NI Balances is fed is from indirects
4106        -- returned by the NI Formula.
4107        -- exceptionally users adjust NI balances in a run or adjustment
4108        -- by giving an individual NI Category Element to an assignment
4109        -- the ni_run_result cursor caters for these two types of
4110        -- results using the optimal N51 index to retreive results.
4111        -- To achieve this it joins first to the element entries
4112        -- Table for a list of NI elements defined in a user table.
4113        begin
4114        g_ni_a_exists := 0;
4115        g_ni_b_exists := 0;
4116        g_ni_c_exists := 0;
4117        g_ni_d_exists := 0;
4118        g_ni_e_exists := 0;
4119        g_ni_f_exists := 0;
4120        g_ni_g_exists := 0;
4121        g_ni_j_exists := 0;
4122        g_ni_l_exists := 0;
4123        g_ni_s_exists := 0;
4124        if g_action_typer is null then -- [ ? check for user table redundant
4125        for l_entry in CSR_ni_entries loop -- { loop through the entries
4126         -- for NI itself look for the indirect results it has produced
4127         if l_entry.element_type_id = g_ni_element_type_id then -- [ NI
4128                 open  CSR_ni_run_results_exist(l_entry.source_id);
4129                 fetch CSR_ni_run_results_exist
4130                         into     l_ni_a_exists_adj
4131                                 ,l_ni_b_exists_adj
4132                                 ,l_ni_c_exists_adj
4133                                 ,l_ni_d_exists_adj
4134                                 ,l_ni_e_exists_adj
4135                                 ,l_ni_f_exists_adj
4136                                 ,l_ni_g_exists_adj
4137                                 ,l_ni_j_exists_adj
4138                                 ,l_ni_l_exists_adj
4139                                 ,l_ni_s_exists_adj;
4140                 close CSR_ni_run_results_exist;
4141                 if l_ni_a_exists_adj = 1 then g_ni_a_exists := 1; end if;
4142                 if l_ni_b_exists_adj = 1 then g_ni_b_exists := 1; end if;
4143                 if l_ni_c_exists_adj = 1 then g_ni_c_exists := 1; end if;
4144                 if l_ni_d_exists_adj = 1 then g_ni_d_exists := 1; end if;
4145                 if l_ni_e_exists_adj = 1 then g_ni_e_exists := 1; end if;
4146                 if l_ni_f_exists_adj = 1 then g_ni_f_exists := 1; end if;
4147                 if l_ni_g_exists_adj = 1 then g_ni_g_exists := 1; end if;
4148                 if l_ni_j_exists_adj = 1 then g_ni_j_exists := 1; end if;
4149                 if l_ni_l_exists_adj = 1 then g_ni_l_exists := 1; end if;
4150                 if l_ni_s_exists_adj = 1 then g_ni_s_exists := 1; end if;
4151         end if; -- ] NI
4152                 if l_entry.element_type_id = g_ni_a_element_type_id
4153                                          then g_ni_a_exists := 1; end if;
4154                 if l_entry.element_type_id = g_ni_b_element_type_id
4155                                          then g_ni_b_exists := 1; end if;
4156                 if l_entry.element_type_id = g_ni_c_element_type_id
4157                                          then g_ni_c_exists := 1; end if;
4158                 if l_entry.element_type_id = g_ni_d_element_type_id
4159                                          then g_ni_d_exists := 1; end if;
4160                 if l_entry.element_type_id = g_ni_e_element_type_id
4161                                          then g_ni_e_exists := 1; end if;
4162                 if l_entry.element_type_id = g_ni_f_element_type_id
4163                                          then g_ni_f_exists := 1; end if;
4164                 if l_entry.element_type_id = g_ni_g_element_type_id
4165                                          then g_ni_g_exists := 1; end if;
4166                 if l_entry.element_type_id = g_ni_j_element_type_id
4167                                          then g_ni_j_exists := 1; end if;
4168                 if l_entry.element_type_id = g_ni_l_element_type_id
4169                                          then g_ni_l_exists := 1; end if;
4170                 if l_entry.element_type_id = g_ni_s_element_type_id
4171                                          then g_ni_s_exists := 1; end if;
4172         end loop; -- } ni_entries loop
4173       end if; -- ]
4174     end;
4175     begin
4176     -- now select initialization in the year
4177     -- initialization results don't have source_id set to the NI Element
4178     -- so for these actions use a more expensive execution plan that
4179     -- retrieves all initialization results in the year and then tests
4180     -- whether any feed the NI Balances. Condition this step out all together
4181     -- if no initialization actions are detected in the year. If no seeded
4182     -- user table exists then also use this cursor
4183     if /* g_initialization_exists = 1 or  */
4184        g_action_typer = 'R' then
4185       --
4186       open  CSR_run_results_exist;
4187       fetch CSR_run_results_exist
4188                         into     l_ni_a_exists_adj
4189                                 ,l_ni_b_exists_adj
4190                                 ,l_ni_c_exists_adj
4191                                 ,l_ni_d_exists_adj
4192                                 ,l_ni_e_exists_adj
4193                                 ,l_ni_f_exists_adj
4194                                 ,l_ni_g_exists_adj
4195                                 ,l_ni_j_exists_adj
4196                                 ,l_ni_l_exists_adj
4197                                 ,l_ni_s_exists_adj;
4198       close CSR_run_results_exist;
4199     end if;
4200     end;
4201   --
4202   --
4203   if l_ni_a_exists_adj = 1 then g_ni_a_exists := 1; end if;
4204   if l_ni_b_exists_adj = 1 then g_ni_b_exists := 1; end if;
4205   if l_ni_c_exists_adj = 1 then g_ni_c_exists := 1; end if;
4206   if l_ni_d_exists_adj = 1 then g_ni_d_exists := 1; end if;
4207   if l_ni_e_exists_adj = 1 then g_ni_e_exists := 1; end if;
4208   if l_ni_f_exists_adj = 1 then g_ni_f_exists := 1; end if;
4209   if l_ni_g_exists_adj = 1 then g_ni_g_exists := 1; end if;
4210   if l_ni_j_exists_adj = 1 then g_ni_j_exists := 1; end if;
4211   if l_ni_l_exists_adj = 1 then g_ni_l_exists := 1; end if;
4212   if l_ni_s_exists_adj = 1 then g_ni_s_exists := 1; end if;
4213  --
4214  end if; -- g_asg_action = p_asg_action.
4215  --
4216 ELSIF l_nitotal_value = 0 AND l_niable_value = 0 THEN
4217  --
4218  -- There are latest balances but they are zero so could be
4219  -- from a previous asg action. The rest of this category's
4220  -- balances are not needed anyway, so return a 0.
4221  --
4222  if P_category = 'A' then g_ni_a_exists := 0; end if;
4223  if P_category = 'B' then g_ni_b_exists := 0; end if;
4224  if P_category = 'C' then g_ni_c_exists := 0; end if;
4225  if P_category = 'D' then g_ni_d_exists := 0; end if;
4226  if P_category = 'E' then g_ni_e_exists := 0; end if;
4227  if P_category = 'F' then g_ni_f_exists := 0; end if;
4228  if P_category = 'G' then g_ni_g_exists := 0; end if;
4229  if P_category = 'J' then g_ni_j_exists := 0; end if;
4230  if P_category = 'L' then g_ni_l_exists := 0; end if;
4231  if P_category = 'S' then g_ni_s_exists := 0; end if;
4232  --
4233 ELSE
4234  --
4235  -- The latest balances are not null or 0, so there must be a
4236  -- balance value for this category, set the individual existance
4237  -- variables due to reset of master return variable below.
4238  --
4239  if P_category = 'A' then g_ni_a_exists := 1; end if;
4240  if P_category = 'B' then g_ni_b_exists := 1; end if;
4241  if P_category = 'C' then g_ni_c_exists := 1; end if;
4242  if P_category = 'D' then g_ni_d_exists := 1; end if;
4243  if P_category = 'E' then g_ni_e_exists := 1; end if;
4244  if P_category = 'F' then g_ni_f_exists := 1; end if;
4245  if P_category = 'G' then g_ni_g_exists := 1; end if;
4246  if P_category = 'J' then g_ni_j_exists := 1; end if;
4247  if P_category = 'L' then g_ni_l_exists := 1; end if;
4248  if P_category = 'S' then g_ni_s_exists := 1; end if;
4249 
4250 END IF; -- (Latest balances)
4251  --
4252  l_return := 0;
4253  if P_category = 'A' then l_return := g_ni_a_exists; end if;
4254  if P_category = 'B' then l_return := g_ni_b_exists; end if;
4255  if P_category = 'C' then l_return := g_ni_c_exists; end if;
4256  if P_category = 'D' then l_return := g_ni_d_exists; end if;
4257  if P_category = 'E' then l_return := g_ni_e_exists; end if;
4258  if P_category = 'F' then l_return := g_ni_f_exists; end if;
4259  if P_category = 'G' then l_return := g_ni_g_exists; end if;
4260  if P_category = 'J' then l_return := g_ni_j_exists; end if;
4261  if P_category = 'L' then l_return := g_ni_l_exists; end if;
4262  if P_category = 'S' then l_return := g_ni_s_exists; end if;
4263  --
4264 return l_return;
4265 end ni_category_exists_in_year;
4266 --
4267 FUNCTION get_master_action_id(p_action_type IN VARCHAR2,
4268                               p_action_id   IN NUMBER)
4269 RETURN NUMBER
4270 IS
4271    l_action_id   number;
4272 BEGIN
4273      l_action_id := null;
4274      if (p_action_type in ('R','Q')) then
4275         select nvl(assact.source_action_id, assact.assignment_action_id)
4276         into   l_action_id
4277         from   pay_assignment_actions assact
4278         where  assact.assignment_action_id = p_action_id;
4279      end if;
4280 
4281      return l_action_id;
4282 END get_master_action_id;
4283 --
4284 --
4285 END hr_gbbal;