DBA Data[Home] [Help]

PACKAGE BODY: APPS.PER_ASG_AGGR

Source


1 PACKAGE BODY per_asg_aggr AS
2 /* $Header: peaggasg.pkb 120.16.12020000.6 2013/04/08 10:23:20 ssarap ship $ */
3 
4 G_WHO_CALLED varchar2(100); /* Bug Fix 9253988 */
5 G_VALIDATION_FAILURE boolean;
6 
7 /*---------------------------------------------------
8               --FUNCTION: assg_aggr_possible
9  Function to check if multiple assignments with
10  same tax district exist for this person.
11  ---------------------------------------------------*/
12  FUNCTION assg_aggr_possible (p_person_id IN NUMBER,
13                               p_effective_date IN DATE,
14                               p_message IN VARCHAR2) RETURN boolean
15  IS
16  l_segment_prev hr_soft_coding_keyflex.segment1%TYPE;
17  l_count_assignments NUMBER;
18  l_count_paye_link   NUMBER;
19  l_same_tax_district BOOLEAN default FALSE;
20  l_same_paye_element_value BOOLEAN default TRUE;
21  l_new_paye_element_value VARCHAR(100) default NULL;
22  l_old_paye_element_value VARCHAR(100) default NULL;
23  l_sys_per_type varchar2(30);
24  l_ni_flag  varchar2(10);
25  l_paye_flag varchar2(10);
26  l_profile_value varchar2(30); -- bug8370225
27 
28  -- Start of Bug 5671777-9
29  l_effective_end_date DATE;
30  l_new_cpe_strat_date DATE;
31  l_old_cpe_strat_date DATE;
32  l_old_assignment_id  NUMBER;
33  l_new_assignment_id  NUMBER;
34  l_old_effective_end_date DATE;
35  l_new_effective_end_date DATE;
36  l_old_effective_start_date DATE;
37  l_new_effective_start_date DATE;
38  -- End of Bug 5671777-9
39 
40  --
41  -- Start of Bug 5671777-9
42  -- Changed the cursor to fecth PAYE agg flag effective end date
43  cursor cur_get_aggr_flag(c_person_id in number,
44                           c_effective_date in date) is
45  select per_information10,effective_end_date
46  from   per_all_people_f
47  where  person_id = c_person_id
48  and    c_effective_date between effective_start_date and effective_end_date;
49  -- End of Bug 5671777-9
50 
51  cursor cur_person_type (c_person_id in number,
52                          c_effective_date in date) is
53   select typ.system_person_type
54   from per_person_types typ,
55        per_all_people_f ppf
56   where ppf.person_id = c_person_id
57   and   ppf.person_type_id = typ.person_type_id
58   and c_effective_date between
59      ppf.effective_start_date and ppf.effective_end_date;
60  --
61 /*Bug-13344652- Modified the cursor cur_rows_assg*/
62  CURSOR cur_rows_assg IS
63  SELECT count(*)
64  FROM per_all_assignments_f
65  WHERE person_id = p_person_id
66 AND ((assignment_type <> 'A' and assignment_type <> 'O')
67          or (assignment_type in ('A','O') and payroll_id is not null))
68  AND p_effective_date BETWEEN effective_start_date AND effective_end_date ;
69 
70  CURSOR cur_tax_reference IS
71   SELECT COUNT(hsck.segment1) Num, hsck.segment1 tax_district
72   FROM hr_soft_coding_keyflex hsck,
73        pay_all_payrolls_f papf,
74        per_all_assignments_f paaf,
75        per_assignment_status_types past
76   WHERE hsck.soft_coding_keyflex_id = papf.soft_coding_keyflex_id
77   AND papf.payroll_id =paaf.payroll_id
78   AND past.assignment_status_type_id = paaf.assignment_status_type_id
79   AND paaf.person_id = p_person_id
80  /*Commented for bug fix 3949536*/
81 --AND past.per_system_status='ACTIVE_ASSIGN'
82   AND p_effective_date BETWEEN paaf.effective_start_date AND paaf.effective_end_date
83   AND p_effective_date BETWEEN papf.effective_start_date AND papf.effective_end_date
84   GROUP BY hsck.segment1;
85 
86   /*BUG 2879391 Added the cursor to compare PAYE info for multiple assignments*/
87   /*BUG 4520393 added joins with pay_all_payrolls_f and hr_soft_coding_keyflex to validate
88     PAYE info only for assignments within the same PAYE reference*/
89 
90   -- Start of BUG 5671777-9
91   -- Added code to fetch PAYE info of the multiple assignments with same CPE
92   --
93 
94   CURSOR cur_paye_element_values(p_tax_district varchar2,p_start_date date,p_end_date date) IS
95   SELECT nvl(min(decode(inv.name, 'Tax Code', eev.screen_entry_value, null)),0)||
96   nvl(min(decode(inv.name, 'Tax Basis', substr(HR_GENERAL.DECODE_LOOKUP('GB_TAX_BASIS',eev.screen_entry_value),1,80),null)),0)||
97   nvl(min(decode(inv.name, 'Refundable', substr(HR_GENERAL.DECODE_LOOKUP('GB_REFUNDABLE',eev.screen_entry_value),1,80),null)),0)||
98   nvl(min(decode(inv.name, 'Pay Previous', eev.screen_entry_value, null)),0)||
99   nvl(min(decode(inv.name, 'Tax Previous', eev.screen_entry_value, null)),0)||
100   nvl(min(decode(inv.name, 'Authority', substr(HR_GENERAL.DECODE_LOOKUP('GB_AUTHORITY',eev.screen_entry_value),1,80),null)),0)||
101   nvl(ele.entry_information1,0)||
102   nvl(ele.entry_information2,0) VALUE,
103   pay_gb_eoy_archive.get_agg_active_start(paa.assignment_id, p_tax_district, greatest(paa.effective_start_date,ppf.effective_start_date)) cpe_start_date,
104   paa.assignment_id assignment_id,
105   eev.effective_start_date effective_start_date,
106   eev.effective_end_date effective_end_date
107   from
108   pay_element_entries_f ele,
109   pay_element_entry_values_f eev,
110   pay_input_values_f inv,
111   pay_element_links_f lnk, pay_element_types_f elt,
112   per_all_assignments_f paa,
113   pay_all_payrolls_f ppf,
114   hr_soft_coding_keyflex scl
115   where ele.element_entry_id = eev.element_entry_id
116   -- and p_effective_date between ele.effective_start_date and ele.effective_end_date
117   and ele.effective_start_date <= p_end_date
118   and ele.effective_end_date >= p_start_date
119   and eev.input_value_id + 0 = inv.input_value_id
120   -- and p_effective_date between eev.effective_start_date and eev.effective_end_date
121   and eev.effective_start_date <= p_end_date
122   and eev.effective_end_date >= p_start_date
123   and inv.element_type_id = elt.element_type_id
124   -- and p_effective_date between inv.effective_start_date and inv.effective_end_date
125   and inv.effective_start_date <= p_end_date
126   and inv.effective_end_date >= p_start_date
127   and ele.element_link_id = lnk.element_link_id
128   and elt.element_type_id = lnk.element_type_id
129   --  and p_effective_date between lnk.effective_start_date and lnk.effective_end_date
130   and lnk.effective_start_date <= p_end_date
131   and lnk.effective_end_date >= p_start_date
132   and elt.element_name = 'PAYE Details'
133   and paa.person_id= p_person_id
134   and ele.assignment_id=paa.assignment_id
135   -- and p_effective_date between elt.effective_start_date and elt.effective_end_date
136   and elt.effective_start_date <= p_end_date
137   and elt.effective_end_date >= p_start_date
138   --  and p_effective_date between paa.effective_start_date and paa.effective_end_date
139   and paa.effective_start_date <= p_end_date
140   and paa.effective_end_date >= p_start_date
141   and scl.segment1=p_tax_district
142   and ppf.soft_coding_keyflex_id=scl.soft_coding_keyflex_id
143   and ppf.payroll_id = paa.payroll_id
144   -- and p_effective_date between ppf.effective_start_date and ppf.effective_end_date
145   and ppf.effective_start_date <= p_end_date
146   and ppf.effective_end_date >= p_start_date
147 
148   and exists ( SELECT 1
149 	       FROM per_all_assignments_f paaf,
150 	            pay_all_payrolls_f papf,
151 		    hr_soft_coding_keyflex hsck,
152 		    per_assignment_status_types past
153 	       WHERE paaf.person_id = p_person_id
154 	       and paaf.assignment_id not in (paa.assignment_id)
155                and paaf.effective_start_date <= p_end_date
156                and paaf.effective_end_date >= p_start_date
157 	       and papf.effective_start_date <= p_end_date
158 	       and papf.effective_end_date >= p_start_date
159 	       and papf.payroll_id = paaf.payroll_id
160 	       and papf.soft_coding_keyflex_id=hsck.soft_coding_keyflex_id
161 	       and hsck.segment1 = scl.segment1
162 	       and pay_gb_eoy_archive.get_agg_active_end(paa.assignment_id, p_tax_district, greatest(paa.effective_start_date,ppf.effective_start_date))
163 	         = pay_gb_eoy_archive.get_agg_active_end(paaf.assignment_id, p_tax_district, greatest(paaf.effective_start_date,papf.effective_start_date))
164 	       and pay_gb_eoy_archive.get_agg_active_start(paa.assignment_id, p_tax_district, greatest(paa.effective_start_date,ppf.effective_start_date))
165 	         = pay_gb_eoy_archive.get_agg_active_start(paaf.assignment_id, p_tax_district, greatest(paaf.effective_start_date,papf.effective_start_date))
166 	       and paaf.assignment_status_type_id = past.assignment_status_type_id
167 	       and past.per_system_status in ('ACTIVE_ASSIGN','SUSP_ASSIGN')
168 	      )
169   group by ele.rowid, scl.segment1,
170   ele.assignment_id,ele.element_entry_id,
171   ele.entry_information_category, ele.entry_information1, ele.entry_information2,
172   ele.effective_start_date, ele.effective_end_date,
173   eev.effective_start_date,eev.effective_end_date,
174   paa.assignment_id,paa.effective_start_date,ppf.effective_start_date
175   order by cpe_start_date,eev.effective_start_date,paa.assignment_id;
176 
177   -- End of Bug 5671777-9
178 
179   CURSOR cur_paye_element_link IS
180   select count(*)
181   from   pay_element_entries_f      ele,
182   	 pay_element_links_f        lnk,
183   	 pay_element_types_f        elt,
184   	 per_all_assignments_f      paa
185   where  elt.element_name    = 'PAYE Details'
186   and    p_effective_date between elt.effective_start_date and elt.effective_end_date
187   and    elt.element_type_id = lnk.element_type_id
188   and    p_effective_date between lnk.effective_start_date and lnk.effective_end_date
189   and    lnk.element_link_id = ele.element_link_id
190   and    p_effective_date between ele.effective_start_date and ele.effective_end_date
191   and    ele.assignment_id   = paa.assignment_id
192   and    paa.person_id       = p_person_id
193   and    p_effective_date between paa.effective_start_date and paa.effective_end_date;
194 
195 BEGIN
196  --
197  open cur_get_aggr_flag(p_person_id, p_effective_date);
198  fetch cur_get_aggr_flag into  l_paye_flag,l_effective_end_date;
199  close cur_get_aggr_flag;
200 
201  -- if the current values is already 'Y' then no need for validation
202  if (l_paye_flag = 'Y')  then
203    return true;
204  end if;
205  --
206  open cur_person_type(p_person_id, p_effective_date);
207  fetch cur_person_type into l_sys_per_type;
208  close cur_person_type;
209  --
210  if l_sys_per_type <> 'EX_EMP' then
211     -- If the Person is an Ex Employee, then no checks below
212     -- necessary as they are given a new assignment on rehire
213     OPEN cur_rows_assg;
214     FETCH cur_rows_assg INTO l_count_assignments;
215     CLOSE cur_rows_assg;
216     --
217     -- check number of asgs for live person.
218   IF l_count_assignments <=1 THEN
219     IF p_message = 'Y' THEN
220     -- start of bug 8370225
221     -- We should igonore the HR_78101_CHK_MULTI_ASSG error message while defaulting the PAYE and NI flags
222     fnd_profile.get('GB_PAYE_NI_AGGREGATION',l_profile_value);
223     if NVL(l_profile_value,'N') <> 'Y' then
224      -- end of bug 8370225
225      /* Bug 9253988. Setting validation failure flag. */
226      if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
227         G_VALIDATION_FAILURE := true;
228      end if;
229      hr_utility.set_message(800,'HR_78101_CHK_MULTI_ASSG');
230      hr_utility.raise_error;
231     END IF;
232     END IF;
233     RETURN FALSE;
234   ELSE
235     --
236   	FOR l_segment_1 IN cur_tax_reference LOOP
237   		--
238   	 	IF l_segment_1.Num > 1 THEN
239   	 		l_same_tax_district:= TRUE;
240                 END IF;
241                 --
242   	END LOOP;
243   	--
244   	IF l_same_tax_district <> TRUE THEN
245   	IF p_message = 'Y' THEN
246           /* Bug 9253988. Setting validation failure flag. */
247           if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
248                G_VALIDATION_FAILURE := true;
249           end if;
250   	  hr_utility.set_message(800,'HR_78102_DIFF_TAX_DIST');
251           hr_utility.raise_error;
252 
253   	END IF;
254   	RETURN FALSE;
255   	END IF;
256   	--
257 
258   	/*BUG 3516114 Added code to check for PAYE Details element link */
259   	OPEN cur_paye_element_link;
260   	FETCH cur_paye_element_link INTO l_count_paye_link;
261   	CLOSE cur_paye_element_link;
262 
263   	IF l_count_paye_link < 1 THEN
264   	  IF p_message = 'Y' THEN
265   	     /* Bug 9253988. Setting validation failure flag. */
266              if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
267                 G_VALIDATION_FAILURE := true;
268              end if;
269              hr_utility.set_message(801,'HR_78110_DIFF_PAYE_VALUES');
270              hr_utility.raise_error;
271 
272     	  END IF;
273   	  RETURN FALSE;
274   	END IF;
275   	--
276 
277   	/*BUG 2879391 Added Code to check that multiple assignments have same PAYE info*/
278 	/* BUG 4520393 Added futher code to check that multiple assignments within SAME PAYE reference
279 	   have same PAYE info*/
280        -- Start of Bug 5671777-9
281        -- Added code to check that multiple assignments with same CPE have sme PAYE info
282 
283         FOR l_tax_ref IN cur_tax_reference LOOP
284           FOR l_paye_values IN cur_paye_element_values(L_TAX_REF.tax_district,p_effective_date,l_effective_end_date) LOOP
285 
286             IF  l_new_paye_element_value is null AND l_old_paye_element_value is null
287             AND l_new_cpe_strat_date is null AND l_old_cpe_strat_date is null THEN
288   	         l_old_paye_element_value := l_paye_values.VALUE ;
289   	         l_old_cpe_strat_date := l_paye_values.cpe_start_date;
290   	         l_old_assignment_id := l_paye_values.assignment_id;
291   	         l_old_effective_start_date := l_paye_values.effective_start_date;
292   	         l_old_effective_end_date := l_paye_values.effective_end_date;
293             ELSE
294   	         l_new_paye_element_value := l_paye_values.VALUE;
295   	         l_new_cpe_strat_date := l_paye_values.cpe_start_date;
296   	         l_new_assignment_id := l_paye_values.assignment_id;
297   	         l_new_effective_start_date := l_paye_values.effective_start_date;
298   	         l_new_effective_end_date := l_paye_values.effective_end_date;
299 
300                 IF l_old_cpe_strat_date = l_new_cpe_strat_date THEN
301                   IF l_old_assignment_id = l_new_assignment_id AND l_old_paye_element_value = l_new_paye_element_value THEN
302                      l_old_effective_end_date := l_new_effective_end_date;
303                   ELSIF l_old_assignment_id = l_new_assignment_id AND l_old_paye_element_value <> l_new_paye_element_value THEN
304                      IF l_old_effective_end_date + 1 = l_new_effective_start_date THEN
305                         l_old_paye_element_value := l_new_paye_element_value;
306                         l_old_effective_start_date := l_new_effective_start_date;
307   	                l_old_effective_end_date := l_new_effective_end_date;
308                      ELSE
309                         l_same_paye_element_value := FALSE;
310                         EXIT;
311                      END IF;
312  	          ELSIF l_old_assignment_id <> l_new_assignment_id AND l_old_paye_element_value = l_new_paye_element_value THEN
313  	                l_old_effective_end_date := greatest(l_new_effective_end_date,l_old_effective_end_date);
314                   ELSIF l_old_assignment_id <> l_new_assignment_id AND l_old_paye_element_value <>l_new_paye_element_value THEN
315   	             IF l_old_effective_end_date + 1 = l_new_effective_start_date THEN
316                         l_old_paye_element_value := l_new_paye_element_value;
317                         l_old_effective_start_date := l_new_effective_start_date;
318   	                l_old_effective_end_date := l_new_effective_end_date;
319                      ELSE
320                         l_same_paye_element_value := FALSE;
321                         EXIT;
322                      END IF;
323                   END IF;
324   	        ELSE
325 		    l_old_paye_element_value := l_new_paye_element_value;
326                     l_old_cpe_strat_date := l_new_cpe_strat_date;
327                     l_old_assignment_id := l_new_assignment_id;
328   	            l_old_effective_start_date := l_new_effective_start_date;
329   	            l_old_effective_end_date := l_new_effective_end_date;
330   	        END IF;
331   	    END IF;
332        	 END LOOP;
333            l_new_paye_element_value := NULL;
334            l_old_paye_element_value := NULL;
335            l_new_cpe_strat_date := NULL;
336            l_old_cpe_strat_date := NULL;
337            l_old_assignment_id := NULL;
338            l_new_assignment_id := NULL;
339            l_old_effective_start_date := NULL;
340            l_new_effective_start_date := NULL;
341            l_old_effective_end_date := NULL;
342            l_new_effective_end_date := NULL;
343         END LOOP;
344 	-- End of Bug 5671777-9
345 
346         IF l_same_paye_element_value <> TRUE THEN
347          IF p_message = 'Y' THEN
348         -- Input values of the Paye Details for multiple assignments is not same
349            /* Bug 9253988. Setting validation failure flag. */
350            if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
351                G_VALIDATION_FAILURE := true;
352            end if;
353            hr_utility.set_message(801,'HR_78110_DIFF_PAYE_VALUES');
354            hr_utility.raise_error;
355          END IF;
356         --
357         RETURN FALSE;
358 	END IF;
359 	RETURN TRUE;
360   	--
361   END IF; -- Count of assignments
362   --
363  else -- The person is an ex employee so this is a rehire,
364       -- return TRUE
365   RETURN TRUE;
366   --
367  end if; -- Ex employee check
368 --
369 END assg_aggr_possible;
370 
371 
372 --Start of Bug 10213888
373 
374 /*
375 Procedure created to get the current date track mode
376 from the PERGBOBJ.fmb to validate the NI aggregation Flag
377 */
378 PROCEDURE set_date_track_mode(l_dt_mode VARCHAR2)
379 IS
380 BEGIN
381   l_datetrack_mode:=l_dt_mode;
382 
383 END;
384 
385 
386 /*
387 Procedure created to validate NI aggregation flag.
388 This procedure is called inside the check Paye Aggregation
389 validation procedure.
390 
391 */
392 -- Procedure for Validating NI aggregation
393  PROCEDURE chk_agg_ni(
394     p_person_id             IN NUMBER,
395     p_effective_date        IN DATE,
396     p_per_information9      IN VARCHAR2,
397     p_per_information10     IN VARCHAR2,
398 	p_curr_ni_agg_flag      IN VARCHAR2,
399 	p_cur_paye_agg_flag     IN VARCHAR2,
400 	p_cur_effective_start_date	IN DATE,
401 	p_cur_effective_end_date 	IN DATE,
402 	p_datetrack_update_mode	IN VARCHAR2 DEFAULT NULL)
403 IS
404 
405 
406   l_ni_payroll_action_count NUMBER;
407   l_prev_ni_flag VARCHAR2(2);
408   l_fut_ni_flag_count NUMBER;
409 
410 
411 
412 	--Cursor to find out the NI flag status in previous date track record
413 	CURSOR csr_prev_ni_flag IS
414 	   SELECT per_information9
415 	   from per_all_people_f
416 	   WHERE person_id = p_person_id
417      AND effective_end_date=p_cur_effective_start_date-1;
418 
419 	 --Cursor to find out the future NI aggregations after the current date range
420 	 CURSOR csr_fut_ni_flag IS
421 	    SELECT count(*)
422 		FROM per_all_people_f
423 		WHERE person_id = p_person_id
424 		AND effective_start_date > p_effective_date
425 		AND  nvl(per_information9,'N')='N';
426 
427 --Cursor to fetch the count of Payroll Actions preformed between the date range specified by NI flag status criteria
428      CURSOR csr_ni_agg_ass
429       IS
430 	  SELECT COUNT(distinct(paa.assignment_id))
431 	  FROM pay_payroll_actions ppa,
432 	  pay_assignment_actions paact,
433 	  per_all_assignments_f paa
434 	  WHERE paa.person_id         = p_person_id
435 	  AND paa.assignment_id       =paact.assignment_id
436 	  AND ppa.payroll_action_id   =paact.payroll_action_id
437 	  AND ppa.action_type        IN ('R','Q')
438 	  AND ppa.action_status='C'
439 	  AND paact.source_action_id IS NOT NULL
440 	  AND ppa.effective_date BETWEEN p_cur_effective_start_date AND p_cur_effective_end_date;
441 
442 
443   BEGIN
444 
445 
446 --The NI validation should only fire if PAYE flags are not changed
447 IF NVL(p_cur_paye_agg_flag,'N')=NVL(p_per_information10,'N') THEN
448 
449 -- Condition to check whether user is trying to change NI flag or not.
450     IF NVL(p_curr_ni_agg_flag,'N') <> NVL(p_per_information9,'N') THEN
451 
452         IF(NVL(p_per_information9,'N')='Y') THEN -- Employee want to check the NI flag
453 
454 	      OPEN csr_fut_ni_flag;
455 		  FETCH csr_fut_ni_flag into l_fut_ni_flag_count;
456 		  CLOSE csr_fut_ni_flag;
457 
458 	   --Checking whethere there exist any future date tracked Non Aggregation record
459 		 IF l_fut_ni_flag_count>0 THEN
460 		    hr_utility.set_message(801,'HR_GB_78151_NI_AGGR_CHK_FUT');
461 			  hr_utility.raise_error;
462 		 END IF;
463 
464 
465         ELSE  -- When trying to uncheck the flag
466 
467 	  -- Validation for UPDATE MODE
468 	           IF p_datetrack_update_mode='UPDATE' or p_datetrack_update_mode= 'UPDATE_OVERRIDE' or p_datetrack_update_mode='UPDATE_CHANGE_INSERT' THEN
469 
470 	              IF to_char(p_effective_date,'DDMM')<>'0604' THEN
471 			         hr_utility.set_message(801,'HR_GB_78153_NI_AGG_UNCK_ST_FUT');
472 					 hr_utility.raise_error;
473 				  END IF;
474 
475 	       --Validation for CORRECTION MODE
476 	           ELSIF p_datetrack_update_mode='CORRECTION' THEN
477 
478 	    -- In correction mode, we check for more than 1 assignments having payroll run in the date range
479 	             OPEN csr_ni_agg_ass;
480 			        FETCH csr_ni_agg_ass into l_ni_payroll_action_count;
481 			     CLOSE csr_ni_agg_ass;
482 
483                  IF  l_ni_payroll_action_count>1 THEN
484 			               hr_utility.set_message(801,'HR_GB_78154_NI_AGG_UNCK_PRL_AC');
485                      hr_utility.raise_error;
486 
487 		          ELSE-- Multiple Assignments don't have payroll runs
488 
489                          OPEN csr_prev_ni_flag;
490 				            FETCH csr_prev_ni_flag into l_prev_ni_flag;
491 			             CLOSE csr_prev_ni_flag;
492 
493 			        	IF nvl(l_prev_ni_flag,'N')<>'N' AND to_char(p_cur_effective_start_date,'DDMM')<>'0604' THEN
494 								   hr_utility.set_message(801,'HR_GB_78153_NI_AGG_UNCK_ST_FUT');
495 									hr_utility.raise_error;
496 				        END IF;
497 			      END IF;
498 	   END IF;
499 
500   END IF;
501 END IF;
502 END IF;
503 
504 END chk_agg_ni;
505 --End of Bug 10213888
506 
507 
508 /* -----------------------------------------------------------
509             --PROCEDURE:check_aggr_assg
510  Procedure to be called through User hook of update_person_api
511  for calling function assg_aggr_possible and checking if 'NI
512  Multiple assignments' flag is 'Y' if aggregate assignment flag
513  is 'Y'
514  -------------------------------------------------------------*/
515 
516 PROCEDURE check_aggr_assg(p_person_id IN NUMBER,
517                            p_effective_date IN DATE,
518                            p_per_information9 IN VARCHAR2,
519                            p_per_information10 IN VARCHAR2,
520                            p_datetrack_update_mode in VARCHAR2 default null)
521  IS
522 
523 -- Start of bug#8370225
524 l_effective_date date;
525 l_cur_agg_paye_flag per_assignment_status_types.per_system_status%type;
526 l_cur_paye_agg_flag per_all_people_f.per_information10%type;
527 l_curr_ni_agg_flag per_all_people_f.per_information9%type;
528 l_cur_effective_start_date date;
529 l_cur_effective_end_date date;
530 l_earliest_tax_year date;
531 l_latest_tax_year date;
532 l_update_mode varchar2(100);
533 l_date_soy date;
534 l_date_eoy date;
535 l_found number;
536 l_tax_pay_asg_td_ytd_dfbid     number;
537 l_tax_pay_per_td_cpe_ytd_dfbid number;
538 l_paye_asg_td_ytd_dfbid        number;
539 l_paye_per_td_cpe_ytd_dfbid    number;
540 l_term_asg_found           number;
541 l_prev_agg_paye_flag       per_all_people_f.per_information10%type;
542 l_prev_effective_start_date date;
543 l_profile_value varchar2(30);
544 L_LOCAL_DATE_TRACE_MODE varchar2(30);
545 
546    --
547    -- Cursor to fetch PAYE agg flag details
548    --
549    cursor cur_person_details(c_person_id number, c_effective_date date) IS
550    select a.per_information10, a.per_information9, a.effective_start_date,a.effective_end_date
551    from   per_all_people_f a
552    where  a.person_id = c_person_id
553    and    c_effective_date between a.effective_start_date and a.effective_end_date;
554 
555    --
556    -- check multiple assignments of the person exists between start of the year and start of change -1
557    -- which shares same CPE and PAYE reference
558    --
559    cursor cur_chk_multiple_asg(c_person_id in number, c_start_date date, c_end_date date) IS
560    select 1
561    from   pay_all_payrolls_f papf,
562           per_all_assignments_f paaf,
563           hr_soft_coding_keyflex hsck,
564 	      per_assignment_status_types past
565    where  paaf.person_id = c_person_id
566    and    paaf.effective_start_date <= c_end_date-1
567    and    paaf.effective_end_date >= c_start_date
568    and    paaf.assignment_status_type_id = past.assignment_status_type_id
569    and    past.per_system_status in ('ACTIVE_ASSIGN','SUSP_ASSIGN')
570    and    papf.payroll_id =paaf.payroll_id
571    and    papf.soft_coding_keyflex_id = hsck.soft_coding_keyflex_id
572    and    c_end_date between papf.effective_start_date and papf.effective_end_date
573    and    exists ( select 1
574    from   pay_all_payrolls_f apf,
575           per_all_assignments_f aaf,
576           hr_soft_coding_keyflex sck,
577 	  per_assignment_status_types ast
578    where  aaf.person_id = c_person_id
579    and    aaf.assignment_id not in (paaf.assignment_id)
580    and    aaf.effective_start_date <= c_end_date-1
581    and    aaf.effective_end_date >= c_start_date
582    and    aaf.assignment_status_type_id = ast.assignment_status_type_id
583    and    ast.per_system_status in ('ACTIVE_ASSIGN','SUSP_ASSIGN')
584    and    apf.payroll_id =aaf.payroll_id
585    and    c_end_date between apf.effective_start_date and apf.effective_end_date
586    and    apf.soft_coding_keyflex_id   = sck.soft_coding_keyflex_id
587    and    sck.segment1 = hsck.segment1
588    AND    pay_gb_eoy_archive.get_agg_active_end(aaf.assignment_id, hsck.segment1, c_end_date)
589      =    pay_gb_eoy_archive.get_agg_active_end(paaf.assignment_id, hsck.segment1, c_end_date)
590    AND    pay_gb_eoy_archive.get_agg_active_start(aaf.assignment_id, hsck.segment1, c_end_date)
591      =    pay_gb_eoy_archive.get_agg_active_start(paaf.assignment_id, hsck.segment1, c_end_date));
592   --
593   -- cursor to fetch earliest and latest payroll actions tax year for this assignment
594   --
595 
596   CURSOR  csr_ear_lat_tax_year(c_assignment_id in number,c_start_date date, c_end_date date) IS
597   select min(ppa.effective_date),
598          max(ppa.effective_date)
599   from   pay_assignment_actions paa,
600          pay_payroll_actions ppa,
601          per_all_assignments_f paaf
602   where  paa.assignment_id = c_assignment_id
603   and    paaf.assignment_id = c_assignment_id
604   and    paa.payroll_action_id  = ppa.payroll_action_id
605   and    ppa.action_type in ('R','Q')
606   and    ppa.effective_date between c_start_date and c_end_date
607   and    paaf.effective_start_date <= c_end_date
608   and    paaf.effective_end_date >= c_start_date
609   and    paaf.payroll_id = ppa.payroll_id
610   order by ppa.effective_date;
611 
612    CURSOR csr_all_assignments(c_person_id in number, c_start_date date, c_end_date date) IS
613       select assignment_id
614       from   per_all_assignments_f
615       where  person_id = c_person_id
616       and    effective_end_date   >= c_start_date
617       and    effective_start_date <= c_end_date;
618 
619    CURSOR csr_asg_per_bal_diff(c_assignment_id number,c_date_eoy date) IS
620      select 1 from dual
621      where  nvl(hr_gbbal.calc_all_balances(c_date_eoy, c_assignment_id, l_tax_pay_asg_td_ytd_dfbid),0) <>
622             nvl(hr_gbbal.calc_all_balances(c_date_eoy, c_assignment_id, l_tax_pay_per_td_cpe_ytd_dfbid),0) OR
623             nvl(hr_gbbal.calc_all_balances(c_date_eoy, c_assignment_id, l_paye_asg_td_ytd_dfbid),0) <>
624             nvl(hr_gbbal.calc_all_balances(c_date_eoy, c_assignment_id, l_paye_per_td_cpe_ytd_dfbid),0);
625 
626    CURSOR cur_defined_balance(c_balance_name varchar2, c_dimension_name varchar2) IS
627      SELECT defined_balance_id
628      FROM   pay_defined_balances
629      WHERE  balance_type_id = (SELECT balance_type_id
630                                FROM   pay_balance_types
631                               WHERE  balance_name = c_balance_name AND legislation_code = 'GB')
632         AND    balance_dimension_id = (SELECT balance_dimension_id
633                                        FROM   pay_balance_dimensions
634                                        WHERE  dimension_name = c_dimension_name AND legislation_code = 'GB');
635  --
636  -- to fetch the agg paye flag from person details
637  --
638    cursor cur_person_dtls(c_person_id number, c_effective_date date) IS
639     select a.per_information10, a.effective_start_date
640     from   per_all_people_f a
641     where  a.person_id = c_person_id
642     and    c_effective_date between a.effective_start_date and a.effective_end_date;
643 
644   --
645   -- to find whether any terminated assignment exists for a person on effective date of change
646   --
647    cursor cur_term_asg_dtls(c_person_id number, c_effective_date date) IS
648      select 1
649      from   per_all_assignments_f a,
650             per_assignment_status_types past
651      where  a.assignment_status_type_id = past.assignment_status_type_id
652      and    past.per_system_status = 'TERM_ASSIGN'
653      and    a.person_id = c_person_id
654      and    c_effective_date between a.effective_start_date and a.effective_end_date;
655 
656 
657 
658  -- End of bug#8370225
659 
660  BEGIN
661 
662   --
663   -- Added for GSI Bug 5472781
664   --
665   -- Start bug 9535747  : perform below validations only when PAYE flag value chnged
666   l_effective_date := p_effective_date;
667   l_update_mode := p_datetrack_update_mode;
668 
669   open cur_person_details(p_person_id, l_effective_date);
670   fetch cur_person_details into l_cur_paye_agg_flag, l_curr_ni_agg_flag, l_cur_effective_start_date,l_cur_effective_end_date;
671   close cur_person_details;
672   -- If API call doesn't have parameter for PAYE aggregation flag, we need assign defatult value.
673   If p_per_information10 = hr_api.g_varchar2 then
674      l_cur_paye_agg_flag := hr_api.g_varchar2;
675   end if;
676 
677   IF nvl(l_cur_paye_agg_flag,'N') <> nvl(p_per_information10,'N') THEN
678  -- End of bug 9535747
679   IF hr_utility.chk_product_install('Oracle Human Resources', 'GB') THEN
680     --
681     --If aggregate assignment flag is 'Y'
682     IF p_per_information10 = 'Y' THEN
683     -- Check if 'NI Multiple assignments' flag is 'Y'
684       IF p_per_information9 = 'Y' THEN
685         -- Check for multiple assignments and same tax district
686         IF NOT assg_aggr_possible (p_person_id , p_effective_date,'Y')  THEN
687         -- start of bug 8370225
688         -- We should igonore error message while defaulting the PAYE and NI flags
689           fnd_profile.get('GB_PAYE_NI_AGGREGATION',l_profile_value);
690           IF NVL(l_profile_value,'N') <> 'Y' then
691         -- End of bug 8370225
692 	    /* Bug 9253988. Setting validation failure flag. */
693             if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
694                G_VALIDATION_FAILURE := true;
695             end if;
696             hr_utility.raise_error;
697 	  END IF;
698         END IF;
699       ELSE
700 
701         -- if 'NI MUltiple assignment flag is not 'Y'
702         -- aggregate assignment flag cannot be 'Y'
703         /* Bug 9253988. Dont raise error when called from set_paye_aggr. */
704         if (nvl(G_WHO_CALLED,'~') <> 'PER_ASG_AGGR.SET_PAYE_AGGR') then
705             hr_utility.set_message(800,'HR_78103_CHK_NI_MULTI_ASSG_FLG');
706 	    hr_utility.raise_error;
707         end if;
708 
709       END IF;
710     END IF;
711    END IF;
712 
713 -- Start of bug#8370225
714 -- If this procedure is called form PERWSHRG.fmb. We are not doing the validations as
715 -- all these validations are preformed in OBJ form. Hence passed p_datetrack_update_mode
716 -- parameter as 'NOVALIDATION' in PERGBOB.fmb
717 
718 if p_datetrack_update_mode <> 'NOVALIDATION' then
719 
720 
721 begin
722 
723 -- while changing the PAYE aggregation flag, we need to ensure that there are no future payroll actions, on
724 -- two (or) more assignment(s) referring a single PAYE Tax district reference(so asg'saggregated).
725 -- If found then we need to raise an error.
726    -- bug 9535747 : commented the below code as aggregation details are already fetched.
727    /* l_effective_date := p_effective_date;
728     l_update_mode := p_datetrack_update_mode;
729 
730     open cur_person_details(p_person_id, l_effective_date);
731     fetch cur_person_details into l_cur_paye_agg_flag, l_cur_effective_start_date,l_cur_effective_end_date;
732     close cur_person_details;*/
733 
734     if nvl(l_cur_paye_agg_flag,'N') <> nvl(p_per_information10,'N') then
735       if l_update_mode = 'CORRECTION' THEN
736          l_effective_date := l_cur_effective_start_date;
737       end if;
738 
739       if l_update_mode = 'UPDATE_OVERRIDE' THEN
740          l_cur_effective_end_date := to_date('31-12-4712','DD-MM-YYYY');
741       end if;
742 
743       If l_effective_date >= to_date('06-04-'||substr(to_char(l_effective_date,'YYYY/MON/DD'),1,4),'DD-MM-YYYY' ) Then
744          l_date_soy := to_date('06-04-'||substr(to_char(l_effective_date,'YYYY/MON/DD'),1,4),'DD-MM-YYYY' ) ;
745          l_date_eoy := to_date('05-04-'||to_char(to_number(substr(to_char(l_effective_date,'YYYY/MON/DD'),1,4))+1 ),'DD-MM-YYYY')  ;
746       Else
747          l_date_soy := to_date('06-04-'||to_char(to_number(substr(to_char(l_effective_date,'YYYY/MON/DD'),1,4))-1 ),'DD-MM-YYYY')  ;
748          l_date_eoy := to_date('05-04-'||substr(to_char(l_effective_date,'YYYY/MON/DD'),1,4),'DD-MM-YYYY') ;
749       End If;
750 
751       -- Check if another assignment of the person exists between start of the year and start of change -1
752       -- which shares same CPE and PAYE reference
753 
754        If l_date_soy < l_effective_date then
755 	  open cur_chk_multiple_asg(p_person_id, l_date_soy, l_effective_date);
756 	  fetch cur_chk_multiple_asg into l_found;
757 
758 	  If cur_chk_multiple_asg%found then
759              /* Bug 9253988. Dont raise error when called from set_paye_aggr. */
760              if (nvl(G_WHO_CALLED,'~') <> 'PER_ASG_AGGR.SET_PAYE_AGGR') then
761                 close cur_chk_multiple_asg;
762                 hr_utility.set_message(800,'HR_GB_78134_MULTI_ASG_CREATION');
763                 hr_utility.raise_error;
764              end if;
765         --hr_utility.raise_error;
766 
767 	  End If;
768 	  close cur_chk_multiple_asg;
769        End if;
770 
771       -- If the date on which change ends is end of a tax years or end of time (31-12-4712) then donothing
772       -- If the date on which change ends is middle of a tax year then raise error
773       If  not ((substr(to_char(l_cur_effective_end_date,'YYYY/MON/DD'),5,11) = substr(to_char(l_date_eoy,'YYYY/MON/DD'),5,11))
774           or  (to_char(l_cur_effective_end_date,'DD-MM-YYYY') = to_char(to_date('31-12-4712','DD-MM-YYYY'),'DD-MM-YYYY'))) Then
775 
776              /* Bug 9253988. Dont raise error when called from set_paye_aggr. */
777              if (nvl(G_WHO_CALLED,'~') <> 'PER_ASG_AGGR.SET_PAYE_AGGR') then
778                 hr_utility.set_message(800,'HR_GB_78135_AGG_PAYE_FLAG_END');
779                 hr_utility.raise_error;
780              end if;
781            --hr_utility.raise_error;
782 
783       End if;
784 
785       open cur_defined_balance('Taxable Pay', '_ASG_TD_YTD');
786       fetch cur_defined_balance into l_tax_pay_asg_td_ytd_dfbid;
787       close cur_defined_balance;
788 
789       open cur_defined_balance('Taxable Pay', '_PER_TD_CPE_YTD');
790       fetch cur_defined_balance into l_tax_pay_per_td_cpe_ytd_dfbid;
791       close cur_defined_balance;
792 
793       open cur_defined_balance('PAYE', '_ASG_TD_YTD');
794       fetch cur_defined_balance into l_paye_asg_td_ytd_dfbid;
795       close cur_defined_balance;
796 
797       open cur_defined_balance('PAYE', '_PER_TD_CPE_YTD');
798       fetch cur_defined_balance into l_paye_per_td_cpe_ytd_dfbid;
799       close cur_defined_balance;
800 
801     -- Check there is no more than one assignment processed for the employee on any
802     -- PAYE Ref between start and end dates of the change,
803       for asg_rec in csr_all_assignments(p_person_id, l_effective_date, l_cur_effective_end_date)
804     --for asg_rec in csr_all_assignments(p_person_id, l_date_soy, l_date_eoy)
805       loop
806         /* Bug 9453542. Change l_effective_date to SOY. */
807         if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
808             l_effective_date := l_date_soy;
809         end if;
810 	open csr_ear_lat_tax_year(asg_rec.assignment_id, l_effective_date, l_cur_effective_end_date);
811         fetch csr_ear_lat_tax_year into l_earliest_tax_year,l_latest_tax_year;
812 	if l_earliest_tax_year is not null and l_latest_tax_year is not null then
813 
814 	 If l_earliest_tax_year >= to_date('06-04-'||substr(to_char(l_earliest_tax_year,'YYYY/MON/DD'),1,4),'DD-MM-YYYY' ) Then
815             l_earliest_tax_year := to_date('05-04-'||to_char(to_number(substr(to_char(l_earliest_tax_year,'YYYY/MON/DD'),1,4))+1 ),'DD-MM-YYYY')  ;
816          Else
817             l_earliest_tax_year := to_date('05-04-'||substr(to_char(l_earliest_tax_year,'YYYY/MON/DD'),1,4),'DD-MM-YYYY') ;
818          End If;
819 
820 	loop
821 	  open csr_asg_per_bal_diff(asg_rec.assignment_id,l_earliest_tax_year);
822           fetch csr_asg_per_bal_diff into l_found;
823           if csr_asg_per_bal_diff%found then
824             close csr_asg_per_bal_diff;
825 
826            /* Bug 9253988. Setting validation failure flag. */
827            if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
828                G_VALIDATION_FAILURE := true;
829            end if;
830            hr_utility.set_message(800,'HR_GB_78133_MULTI_PRL_ACTIONS');
831            hr_utility.raise_error;
832 
833           end if;
834           close csr_asg_per_bal_diff;
835 	  EXIT when l_earliest_tax_year >= l_latest_tax_year;
836 	  l_earliest_tax_year :=
837 	  to_date(substr(to_char(l_earliest_tax_year,'dd/mm/yyyy'),1,6)||
838 	  to_char(to_number(substr(to_char(l_earliest_tax_year,'dd/mm/yyyy'),7,10))+1),'dd/mm/yyyy');
839         end loop;
840 	end if;
841 	close csr_ear_lat_tax_year;
842       end loop;
843     end if;
844 
845              l_effective_date := p_effective_date;
846 
847              open cur_person_dtls(p_person_id, l_effective_date);
848              fetch cur_person_dtls into l_cur_agg_paye_flag, l_cur_effective_start_date;
849              close cur_person_dtls;
850              --
851              -- when the date of change is from 06-04 and
852              -- the current Agg. PAYE flag = N and new Agg PAYE flag = Y then we need to check
853              -- for any terminated asg's on that date.
854              -- in the correction datetrack mode, we have to consider the effective start date as
855              -- effective date(date of change)
856              --
857              if nvl(l_cur_agg_paye_flag,'N') <> nvl(p_per_information10,'N') and
858                 to_char(l_effective_date,'dd-mm') = '06-04' and l_update_mode <> 'CORRECTION' then
859 
860                 open cur_term_asg_dtls(p_person_id, l_effective_date);
861                 fetch cur_term_asg_dtls into l_term_asg_found;
862                 if cur_term_asg_dtls%found then
863                    close cur_term_asg_dtls;
864                    /* Bug 9253988. Setting validation failure flag. */
865                    if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
866                       G_VALIDATION_FAILURE := true;
867                    end if;
868                    hr_utility.set_message(800,'HR_GB_78129_TERM_ASG_FOUND_SOY');
869                    hr_utility.set_message_token('AGG_START_DATE', fnd_date.date_to_displaydate(l_effective_date));
870                    hr_utility.raise_error;
871 
872                 end if;
873                 close cur_term_asg_dtls;
874              elsif nvl(l_cur_agg_paye_flag,'N') <> nvl(p_per_information10,'N') and
875                 to_char(l_cur_effective_start_date,'dd-mm') = '06-04' and l_update_mode = 'CORRECTION' then
876                 --
877                 -- if datetrack mode is correction and from SOY then check for the previous day aggregation flag,
878                 -- if the flag is Y; then we should not stop this aggregation flag change from N to Y
879                 --
880                 open cur_person_dtls(p_person_id, l_cur_effective_start_date-1);
881                 fetch cur_person_dtls into l_prev_agg_paye_flag, l_prev_effective_start_date;
882                 close cur_person_dtls;
883                 if nvl(l_prev_agg_paye_flag,'N') <> nvl(p_per_information10,'N') then
884                   open cur_term_asg_dtls(p_person_id, l_cur_effective_start_date);
885                   fetch cur_term_asg_dtls into l_term_asg_found;
886                   if cur_term_asg_dtls%found then
887                      close cur_term_asg_dtls;
888                      /* Bug 9253988. Setting validation failure flag. */
889                      if (nvl(G_WHO_CALLED,'~') = 'PER_ASG_AGGR.SET_PAYE_AGGR') then
890                         G_VALIDATION_FAILURE := true;
891                      end if;
892                      hr_utility.set_message(800,'HR_GB_78129_TERM_ASG_FOUND_SOY');
893                      hr_utility.set_message_token('AGG_START_DATE', fnd_date.date_to_displaydate(l_cur_effective_start_date));
894                      hr_utility.raise_error;
895                      --hr_utility.raise_error;
896                   end if;
897                   close cur_term_asg_dtls;
898                 end if;
899              end if;
900         end;
901      end if;
902    -- End of bug#8370225
903     else
904    	--Start of 10213888
905 
906 	--The call to NI validation will be performed only in case when there is no change in PAYE Validation
907 	--Else all validation willl be done in PAYE Validation Logic
908 
909 	-- If API call doesn't have parameter for PAYE aggregation flag, we need assign defatult value.
910   If p_per_information9 = hr_api.g_varchar2 then
911      l_curr_ni_agg_flag := hr_api.g_varchar2;
912   end if;
913 
914   IF p_datetrack_update_mode <>'NOVALIDATION' THEN
915       l_local_date_trace_mode:=p_datetrack_update_mode;
916   ELSE
917     l_local_date_trace_mode:=l_datetrack_mode;
918   END IF;
919 
920 	  chk_agg_ni(
921 		    	 p_person_id             =>p_person_id,
922 			     p_effective_date        =>p_effective_date,
923 			     p_per_information9      =>p_per_information9,
924 			     p_per_information10     =>p_per_information10,
925 				 p_curr_ni_agg_flag      =>l_curr_ni_agg_flag,
926 				 p_cur_paye_agg_flag     =>l_cur_paye_agg_flag,
927 				 p_cur_effective_start_date =>l_cur_effective_start_date,
928 				 p_cur_effective_end_date   =>l_cur_effective_end_date,
929 		  	 p_datetrack_update_mode =>l_local_date_trace_mode);
930 
931 	--End of 10213888
932 
933    end if; -- bug 9535747
934  END check_aggr_assg;
935 --
936 /* Procedure Name: set_paye_aggr
937    Details:
938    This procedure is After Process hook for CREATE_SECONDARY_ASSIGNMENT module.
939    When profile option is set, and secondary assignment is created, then PAYE
940    Aggregation flag should be set by default, provided the PAYE Agg validations
941    are successful.
942 
943    When profile option is set to "NI", then NI Aggregation flag should be set by
944    default, provided NI Agg validations are successful.
945 */
946 PROCEDURE set_paye_aggr(p_person_id IN NUMBER,
947                           p_effective_date IN DATE,
948                           p_assignment_id IN NUMBER,
949                           p_payroll_id IN NUMBER)
950 IS
951 /* Cursor to identify if PAYE flag is set or not */
952  cursor cur_get_aggr_flag(c_person_id in number,
953                           c_effective_date in date) is
954  select per_information10, object_version_number, employee_number
955  from   per_all_people_f
956  where  person_id = c_person_id
957  and    c_effective_date between effective_start_date and effective_end_date;
958 
959  /* Cursor to identify if NI flag is set or not */
960  cursor cur_get_ni_aggr_flag(c_person_id in number,
961                           c_effective_date in date) is
962  select per_information9
963  from   per_all_people_f
964  where  person_id = c_person_id
965  and    c_effective_date between effective_start_date and effective_end_date;
966 
967 /* Get date track records from per_all_people_f, including and after effective date*/
968  cursor people_dt_records(c_person_id in number,
969                           c_effective_date in date) is
970  select person_id, effective_start_date, effective_end_date,
971  per_information9,  per_information10, full_name, object_version_number
972  from per_all_people_f
973  where person_id=c_person_id
974  and effective_end_date >= c_effective_date
975  order by effective_start_date;
976 
977 /* Identify the number of assignments for the person_id*/
978  cursor cur_asg_count(c_person_id in number,
979                           c_effective_date in date) is
980   select count (distinct assignment_id)
981   from per_all_assignments_f
982   where person_id = c_person_id
983   and c_effective_date between effective_start_date and effective_end_date;
984 
985 /* Identify the TD details of the assignment newly created*/
986  cursor get_curr_td_info(c_assignment_id in number,
987                           c_effective_date in date) is
988   SELECT --COUNT(hsck.segment1) Num,
989   hsck.segment1 tax_district
990   FROM hr_soft_coding_keyflex hsck,
991        pay_all_payrolls_f papf,
992        per_all_assignments_f paaf
993   WHERE paaf.assignment_id= c_assignment_id
994   AND papf.payroll_id =paaf.payroll_id
995   AND hsck.soft_coding_keyflex_id = papf.soft_coding_keyflex_id
996   AND c_effective_date BETWEEN paaf.effective_start_date AND paaf.effective_end_date
997   AND c_effective_date BETWEEN papf.effective_start_date AND papf.effective_end_date
998   GROUP BY hsck.segment1;
999 
1000 /* Get PAYE Input values of assignment eligible for aggregation with newly created assg. */
1001  cursor get_paye_details(c_person_id in number,
1002                          c_tax_ref in varchar2,
1003                          c_effective_date in date,
1004                          c_assignment_id in number) is
1005  SELECT distinct
1006                 ppev.TAX_CODE,
1007                 ppev.Tax_Basis,
1008                 ppev.Pay_Previous,
1009                 ppev.Tax_Previous,
1010                 ppev.Refundable,
1011                 ppev.Authority,
1012 				P6_iss_date,
1013 				P6_msg_date
1014            FROM (SELECT min(decode(inv.name, 'Tax Code', eev.screen_entry_value, null)) Tax_Code,
1015                         min(decode(inv.name, 'Tax Basis', eev.screen_entry_value, null)) Tax_Basis,
1016                         min(decode(inv.name, 'Refundable', eev.screen_entry_value, null)) Refundable,
1017                         min(decode(inv.name, 'Pay Previous', nvl(eev.screen_entry_value,0), null)) Pay_Previous,
1018                         min(decode(inv.name, 'Tax Previous', nvl(eev.screen_entry_value,0), null)) Tax_Previous,
1019                         min(decode(inv.name, 'Authority', eev.screen_entry_value, null)) Authority,
1020 						min(ele.entry_information1) P6_iss_date,
1021 						min(ele.entry_information2) P6_msg_date
1022                    FROM pay_element_entries_f ele,
1023                         pay_element_entry_values_f eev,
1024                         pay_input_values_f inv,
1025                         pay_element_links_f lnk,
1026                         pay_element_types_f elt,
1027                         pay_all_payrolls_f papf,
1028                         per_all_assignments_f paaf,
1029                         hr_soft_coding_keyflex hsck
1030                   WHERE paaf.person_id = c_person_id
1031                     AND c_effective_date BETWEEN paaf.effective_start_date AND paaf.effective_end_date
1032                     AND paaf.payroll_id = papf.payroll_id
1033                     AND c_effective_date BETWEEN papf.effective_start_date AND papf.effective_end_date
1034                     AND papf.soft_coding_keyflex_id=hsck.soft_coding_keyflex_id
1035                     AND hsck.segment1 = c_tax_ref
1036                     AND ele.assignment_id=paaf.assignment_id
1037                     AND c_effective_date between ele.effective_start_date and ele.effective_end_date
1038                     AND ele.element_entry_id = eev.element_entry_id
1039                     AND eev.input_value_id + 0 = inv.input_value_id
1040                     AND c_effective_date between eev.effective_start_date and eev.effective_end_date
1041                     AND inv.element_type_id = elt.element_type_id
1042                     AND c_effective_date between inv.effective_start_date and inv.effective_end_date
1043                     AND ele.element_link_id = lnk.element_link_id
1044                     AND c_effective_date between lnk.effective_start_date and lnk.effective_end_date
1045                     AND elt.element_name = 'PAYE Details'
1046                     AND elt.legislation_code = 'GB'
1047                     AND c_effective_date between elt.effective_start_date and elt.effective_end_date
1048                     -- AND pay_p45_pkg.PAYE_SYNC_P45_ISSUED_FLAG(paaf.assignment_id,c_effective_date) = 'N'
1049                     AND paaf.assignment_id <> c_assignment_id
1050                     AND pay_gb_eoy_archive.get_agg_active_start(paaf.assignment_id, c_tax_ref,c_effective_date) =
1051                         pay_gb_eoy_archive.get_agg_active_start(c_assignment_id, c_tax_ref,c_effective_date)
1052                     AND pay_gb_eoy_archive.get_agg_active_end(paaf.assignment_id, c_tax_ref,c_effective_date) =
1053                         pay_gb_eoy_archive.get_agg_active_end(c_assignment_id, c_tax_ref,c_effective_date)
1054                     ) ppev
1055                  where ppev.TAX_CODE is not null
1056                    and ppev.Tax_Basis is not null
1057                    and ppev.Refundable is not null;
1058 
1059 /* Get current assignment PAYE Details element input values */
1060   cursor current_asg_paye_details(c_assignment_id in number, c_effective_date in date) is
1061   SELECT       ele.element_entry_id element_entry_id,
1062                min(decode(inv.name, 'Tax Code', eev.screen_entry_value, null)) Tax_Code,
1063                min(decode(inv.name, 'Tax Code', eev.input_value_id, null)) Tax_Code_iv_id,
1064                min(decode(inv.name, 'Tax Basis', eev.screen_entry_value, null)) Tax_Basis,
1065                min(decode(inv.name, 'Tax Basis', eev.input_value_id, null)) Tax_Basis_iv_id,
1066                min(decode(inv.name, 'Refundable', eev.screen_entry_value, null)) Refundable,
1067                min(decode(inv.name, 'Refundable', eev.input_value_id, null)) Refundable_iv_id,
1068                min(decode(inv.name, 'Pay Previous', nvl(eev.screen_entry_value,0), null)) Pay_Previous,
1069                min(decode(inv.name, 'Pay Previous', eev.input_value_id, null)) Pay_Previous_iv_id,
1070                min(decode(inv.name, 'Tax Previous', nvl(eev.screen_entry_value,0), null)) Tax_Previous,
1071                min(decode(inv.name, 'Tax Previous', eev.input_value_id, null)) Tax_Previous_iv_id,
1072                min(decode(inv.name, 'Authority', eev.screen_entry_value, null)) Authority,
1073                min(decode(inv.name, 'Authority', eev.input_value_id, null)) Authority_iv_id,
1074 			   min(ele.entry_information1) P6_iss_date,
1075 			   min(ele.entry_information2) P6_msg_date
1076           FROM pay_element_entries_f ele,
1077                pay_element_entry_values_f eev,
1078                pay_input_values_f inv,
1079                pay_element_links_f lnk,
1080                pay_element_types_f elt,
1081                per_all_assignments_f paaf
1082          WHERE ele.element_entry_id = eev.element_entry_id
1083            AND c_effective_date between ele.effective_start_date and ele.effective_end_date
1084            AND eev.input_value_id + 0 = inv.input_value_id
1085            AND c_effective_date between eev.effective_start_date and eev.effective_end_date
1086            AND inv.element_type_id = elt.element_type_id
1087            AND c_effective_date between inv.effective_start_date and inv.effective_end_date
1088            AND ele.element_link_id = lnk.element_link_id
1089            AND c_effective_date between lnk.effective_start_date and lnk.effective_end_date
1090            AND elt.element_name = 'PAYE Details'
1091            AND elt.legislation_code = 'GB'
1092            AND c_effective_date between elt.effective_start_date and elt.effective_end_date
1093            AND ele.assignment_id=paaf.assignment_id
1094            AND c_effective_date BETWEEN paaf.effective_start_date AND paaf.effective_end_date
1095            AND paaf.assignment_id = c_assignment_id
1096            group by ele.element_entry_id;
1097 
1098 /* Get the lookup values and meaning */
1099 cursor get_tax_basis_code(c_lookup_type varchar2, c_lookup_code varchar2) is
1100 select meaning from hr_lookups
1101 where lookup_type=c_lookup_type
1102 and lookup_code=c_lookup_code;
1103 
1104 --Cursor to fetch the count of Payroll Actions preformed between the date range specified by NI flag status criteria
1105    CURSOR csr_ni_agg_ass(p_effective_start_date date, p_effective_end_date date)
1106       IS
1107 	  SELECT COUNT(distinct(paa.assignment_id))
1108 	  FROM pay_payroll_actions ppa,
1109 	  pay_assignment_actions paact,
1110 	  per_all_assignments_f paa
1111 	  WHERE paa.person_id         = p_person_id
1112 	  AND paa.assignment_id       =paact.assignment_id
1113 	  AND ppa.payroll_action_id   =paact.payroll_action_id
1114 	  AND ppa.action_type        IN ('R','Q')
1115 	  AND ppa.action_status='C'
1116 	  AND paact.source_action_id IS NOT NULL
1117 	  AND ppa.effective_date BETWEEN p_effective_start_date AND p_effective_end_date;
1118 
1119 /* Get date track records from per_all_people_f, including and after effective date*/
1120 --Modified the Cursor to fetch Employee_number for the Bug 13323723
1121 CURSOR people_dt_records_desc(c_person_id IN NUMBER, c_effective_date IN DATE)
1122   IS
1123     SELECT person_id,
1124 			employee_number, --Added for Bug 13323723
1125       effective_start_date,
1126       effective_end_date,
1127       per_information9,
1128       per_information10,
1129       full_name,
1130       object_version_number
1131     FROM per_all_people_f
1132     WHERE person_id         =c_person_id
1133     AND effective_end_date >= c_effective_date
1134     ORDER BY effective_start_date desc;
1135 
1136 l_proc varchar2(30) := 'PER_ASG_AGGR.SET_PAYE_AGGR: ';
1137 
1138 l_paye_profile varchar2(30);
1139 l_paye_agg varchar2(2) := 'N';
1140 l_ni_agg varchar2(2) := 'N';
1141 l_obj_version_num number;
1142 l_employee_number varchar2(50);
1143 
1144 l_asg_count number := 0;
1145 l_curr_tax_district varchar2(30);
1146 l_same_paye_det_count number := 0;
1147 
1148 r_curr_asg_paye current_asg_paye_details%rowtype;
1149 r_agg_paye get_paye_details%rowtype;
1150 
1151 l_person_effective_date date;
1152 
1153 l_pers_dt_mode varchar2(30);
1154 l_effective_start_date date;
1155 l_effective_end_date date;
1156 l_full_name per_all_people_f.full_name%type;
1157 l_comment_id per_all_people_f.comment_id%type;
1158 l_name_combination_warning boolean;
1159 l_assign_payroll_warning boolean;
1160 l_orig_hire_warning boolean;
1161 
1162 l_soy date;
1163 l_eot date;
1164 l_ni_asg_count number;
1165 
1166 BEGIN
1167  hr_utility.set_location(' Entering:'||l_proc, 10);
1168 
1169  savepoint start_agg_flag;
1170  G_VALIDATION_FAILURE := false;
1171  G_WHO_CALLED := null;
1172 
1173  fnd_profile.get('GB_DEFAULT_AGG_FLAG',l_paye_profile);
1174 
1175  IF (NVL(l_paye_profile,'~') = 'NI') THEN
1176 
1177 	open cur_get_ni_aggr_flag(p_person_id, p_effective_date);
1178     fetch cur_get_ni_aggr_flag into  l_ni_agg;
1179     close cur_get_ni_aggr_flag;
1180 
1181 
1182 	IF (nvl(l_ni_agg,'N') <> 'Y') then
1183 	hr_utility.set_location('In setting NI Aggregation flag',100);
1184 		IF p_effective_date >= to_date('06-04-'||TO_CHAR(p_effective_date,'YYYY'),'DD-MM-YYYY') THEN
1185 			l_soy					:= to_date('06-04-'||SUBSTR(TO_CHAR(p_effective_date,'YYYY/MON/DD'),1,4),'DD-MM-YYYY');
1186 	  ELSE
1187 		l_soy        := to_date('06-04-'||TO_CHAR(to_number(SUBSTR(TO_CHAR(p_effective_date,'YYYY/MON/DD'),1,4))-1 ),'DD-MM-YYYY') ;
1188 	  END IF;
1189 	l_eot := hr_api.g_eot;
1190 	OPEN csr_ni_agg_ass(l_soy, l_eot);
1191 	FETCH csr_ni_agg_ass into l_ni_asg_count;
1192 	CLOSE csr_ni_agg_ass;
1193 
1194    IF  l_ni_asg_count <= 1 THEN
1195     hr_utility.set_location('Came inside if condition of check_ni_aggr',66);
1196     l_person_effective_date  := p_effective_date;
1197     FOR rec                  IN people_dt_records_desc(p_person_id, p_effective_date)
1198     LOOP
1199       if rec.effective_start_date < p_effective_date then
1200 				if rec.effective_end_date = hr_api.g_eot then
1201 					l_pers_dt_mode           := 'UPDATE';
1202 				else
1203 					l_pers_dt_mode := 'UPDATE_CHANGE_INSERT';
1204 				end if;
1205 				l_person_effective_date := p_effective_date;
1206 			else
1207 				l_pers_dt_mode := 'CORRECTION';
1208 				l_person_effective_date := rec.effective_start_date;
1209 			end if;
1210 			hr_utility.set_location('Updating Person details :'||p_person_id||', l_person_effective_date'||l_person_effective_date, 80);
1211       /* Call API to update NI Agg flag, this will fire validations from check_aggr_assg. */
1212 
1213 	  l_employee_number :=rec.employee_number;   --Added for Bug 13323723
1214       hr_person_api.update_person(p_validate => false
1215 	  ,p_effective_date => l_person_effective_date
1216 	  ,p_datetrack_update_mode => l_pers_dt_mode
1217 	  ,p_person_id => p_person_id
1218 	  ,p_object_version_number => rec.object_version_number
1219 	  ,p_employee_number => l_employee_number
1220 	  ,p_effective_start_date => l_effective_start_date
1221 	  ,p_effective_end_date => l_effective_end_date
1222 	  ,p_per_information9 => 'Y'
1223 	  ,p_full_name => rec.full_name
1224 	  ,p_comment_id => l_comment_id
1225 	  ,p_name_combination_warning => l_name_combination_warning
1226 	  ,p_assign_payroll_warning => l_assign_payroll_warning
1227 	  ,p_orig_hire_warning => l_orig_hire_warning );
1228     END LOOP; -- Records in per_all_people_f which need to be updated.
1229     hr_utility.set_location(l_proc, 90);
1230 	ELSE
1231 		  hr_utility.set_location(l_proc, 95);
1232   		  G_VALIDATION_FAILURE := true;
1233 		  hr_utility.set_message(801,'HR_GB_78155_NI_AGG_FTR_MLT_ASG');
1234 		  hr_utility.raise_error;
1235     END IF;
1236 	END IF;--NI Flag Set Already
1237 
1238  elsif (nvl(l_paye_profile,'~') = 'PAYE') then
1239 
1240     hr_utility.set_location(l_proc, 20);
1241     open cur_get_aggr_flag(p_person_id, p_effective_date);
1242     fetch cur_get_aggr_flag into  l_paye_agg, l_obj_version_num, l_employee_number;
1243     close cur_get_aggr_flag;
1244 
1245     if (nvl(l_paye_agg,'N') <> 'Y') then
1246 
1247       hr_utility.set_location(l_proc, 25);
1248       open cur_asg_count(p_person_id, p_effective_date);
1249       fetch cur_asg_count into  l_asg_count;
1250       close cur_asg_count;
1251 
1252       /* Check if this is the secondary assignment */
1253       if (l_asg_count > 1) then
1254 
1255         hr_utility.set_location(l_proc, 30);
1256         G_WHO_CALLED := 'PER_ASG_AGGR.SET_PAYE_AGGR';
1257 
1258         if p_payroll_id is null then
1259            hr_utility.set_message(800,'HR_78102_DIFF_TAX_DIST');
1260            G_VALIDATION_FAILURE := true;
1261            hr_utility.raise_error;
1262         end if;
1263         hr_utility.set_location(l_proc, 35);
1264 
1265         open get_curr_td_info(p_assignment_id, p_effective_date);
1266         fetch get_curr_td_info into  l_curr_tax_district;
1267         close get_curr_td_info;
1268 
1269         if l_curr_tax_district is null then
1270            hr_utility.set_message(800,'HR_78102_DIFF_TAX_DIST');
1271            G_VALIDATION_FAILURE := true;
1272            hr_utility.raise_error;
1273         end if;
1274         hr_utility.set_location(l_proc, 40);
1275 
1276         open current_asg_paye_details(p_assignment_id, p_effective_date);
1277         fetch current_asg_paye_details into r_curr_asg_paye;
1278         close current_asg_paye_details;
1279         hr_utility.set_location(l_proc, 45);
1280 
1281         for rec_paye in get_paye_details(p_person_id, l_curr_tax_district, p_effective_date, p_assignment_id)
1282         loop
1283             /* Multiple PAYE details for the same Tax district, then error */
1284             if (l_same_paye_det_count = 1) then
1285                hr_utility.set_message(801,'HR_78110_DIFF_PAYE_VALUES');
1286                G_VALIDATION_FAILURE := true;
1287                hr_utility.raise_error;
1288             end if;
1289             l_same_paye_det_count := l_same_paye_det_count + 1;
1290             r_agg_paye.Tax_Code := rec_paye.Tax_Code;
1291             r_agg_paye.Tax_Basis := rec_paye.Tax_Basis;
1292             r_agg_paye.Refundable := rec_paye.Refundable;
1293             r_agg_paye.Pay_Previous := rec_paye.Pay_Previous;
1294             r_agg_paye.Tax_Previous := rec_paye.Tax_Previous;
1295             r_agg_paye.Authority := rec_paye.Authority;
1296 			r_agg_paye.P6_iss_date := rec_paye.P6_iss_date;
1297 			r_agg_paye.P6_msg_date := rec_paye.P6_msg_date;
1298         end loop;
1299 
1300         if (l_same_paye_det_count = 0) then
1301            hr_utility.set_message(800,'HR_78102_DIFF_TAX_DIST');
1302            G_VALIDATION_FAILURE := true;
1303            hr_utility.raise_error;
1304         end if;
1305         hr_utility.set_location(l_proc, 50);
1306 
1307         open get_tax_basis_code('GB_TAX_BASIS', r_agg_paye.Tax_Basis);
1308         fetch get_tax_basis_code into r_agg_paye.Tax_Basis;
1309         close get_tax_basis_code;
1310         open get_tax_basis_code('GB_TAX_BASIS', r_curr_asg_paye.Tax_Basis);
1311         fetch get_tax_basis_code into r_curr_asg_paye.Tax_Basis;
1312         close get_tax_basis_code;
1313 
1314         open get_tax_basis_code('GB_REFUNDABLE', r_agg_paye.Refundable);
1315         fetch get_tax_basis_code into r_agg_paye.Refundable;
1316         close get_tax_basis_code;
1317         open get_tax_basis_code('GB_REFUNDABLE', r_curr_asg_paye.Refundable);
1318         fetch get_tax_basis_code into r_curr_asg_paye.Refundable;
1319         close get_tax_basis_code;
1320 
1321         hr_utility.set_location(l_proc, 60);
1322         if ((nvl(r_agg_paye.Tax_Code,'~') <> nvl(r_curr_asg_paye.Tax_Code,'~')) or
1323             (nvl(r_agg_paye.Tax_Basis,'~') <> nvl(r_curr_asg_paye.Tax_Basis,'~')) or
1324             (nvl(r_agg_paye.Refundable,'~') <> nvl(r_curr_asg_paye.Refundable,'~')) or
1325             (nvl(r_agg_paye.Pay_Previous,'~') <> nvl(r_curr_asg_paye.Pay_Previous,'~')) or
1326             (nvl(r_agg_paye.Tax_Previous,'~') <> nvl(r_curr_asg_paye.Tax_Previous,'~')) or
1327             (nvl(r_agg_paye.Authority,'~') <> nvl(r_curr_asg_paye.Authority,'~')) or
1328 			(nvl(r_agg_paye.P6_iss_date,'~') <> nvl(r_curr_asg_paye.P6_iss_date,'~')) or
1329 			(nvl(r_agg_paye.P6_msg_date,'~') <> nvl(r_curr_asg_paye.P6_msg_date,'~'))
1330 			) then
1331           hr_utility.set_location(l_proc, 70);
1332           hr_entry_api.update_element_entry(p_dt_update_mode => 'CORRECTION',
1333                             p_session_date  => p_effective_date,
1334                             p_element_entry_id => r_curr_asg_paye.element_entry_id,
1335                             p_input_value_id1 => r_curr_asg_paye.Tax_Code_iv_id,
1336                             p_input_value_id2 => r_curr_asg_paye.Tax_Basis_iv_id,
1337                             p_input_value_id3 => r_curr_asg_paye.Pay_Previous_iv_id,
1338                             p_input_value_id4 => r_curr_asg_paye.Tax_Previous_iv_id,
1339                             p_input_value_id5 => r_curr_asg_paye.Refundable_iv_id,
1340                             p_input_value_id6 => r_curr_asg_paye.Authority_iv_id,
1341                             p_entry_value1 => r_agg_paye.Tax_Code,
1342                             p_entry_value2 => r_agg_paye.Tax_Basis,
1343                             p_entry_value3 => r_agg_paye.Pay_Previous,
1344                             p_entry_value4 => r_agg_paye.Tax_Previous,
1345                             p_entry_value5 => r_agg_paye.Refundable,
1346                             p_entry_value6 => r_agg_paye.Authority,
1347 							p_entry_information_category => 'GB_PAYE',
1348 							p_entry_information1 => r_agg_paye.P6_iss_date,
1349 							p_entry_information2 => r_agg_paye.P6_msg_date
1350 							);
1351 
1352         end if;
1353 
1354         l_person_effective_date := p_effective_date;
1355 
1356         hr_utility.set_location(l_proc, 80);
1357         for rec in people_dt_records(p_person_id, p_effective_date)
1358         loop
1359           /* From second iteration, effective date is set to effec_start_date of the record. */
1360           if (l_person_effective_date <> p_effective_date) then
1361              l_person_effective_date := rec.effective_start_date;
1362           end if;
1363 
1364           /* Idenfity the date track mode to be used. */
1365           if (rec.effective_start_date <> l_person_effective_date) then
1366              if (rec.effective_end_date = hr_api.g_eot) then
1367                 l_pers_dt_mode := 'UPDATE';
1368              else
1369                 l_pers_dt_mode := 'UPDATE_CHANGE_INSERT';
1370              end if;
1371           else
1372              l_pers_dt_mode := 'CORRECTION';
1373           end if;
1374 
1375           /* Call API to update PAYE Agg flag, this will fire validations from check_aggr_assg. */
1376           hr_person_api.update_person(p_validate => false
1377           ,p_effective_date  =>  l_person_effective_date
1378           ,p_datetrack_update_mode => l_pers_dt_mode
1379           ,p_person_id => p_person_id
1380           ,p_object_version_number => rec.object_version_number
1381           ,p_employee_number => l_employee_number
1382           ,p_effective_start_date => l_effective_start_date
1383           ,p_effective_end_date => l_effective_end_date
1384           ,p_per_information9 => 'Y'
1385           ,p_per_information10 => 'Y'
1386           ,p_full_name => rec.full_name
1387           ,p_comment_id => l_comment_id
1388           ,p_name_combination_warning => l_name_combination_warning
1389           ,p_assign_payroll_warning => l_assign_payroll_warning
1390           ,p_orig_hire_warning => l_orig_hire_warning
1391           );
1392 
1393           /* Reset/change the variable */
1394           l_person_effective_date := rec.effective_start_date;
1395 
1396         end loop; -- Records in per_all_people_f which need to be updated.
1397 
1398       hr_utility.set_location(l_proc, 90);
1399       end if; -- If secondary assignment
1400     end if; -- PAYE Agg not set already
1401  end if; -- Profile set
1402 hr_utility.set_location(' Leaving:'||l_proc, 100);
1403 
1404 exception
1405 when others then
1406 if G_VALIDATION_FAILURE then
1407    rollback to start_agg_flag;
1408    hr_utility.set_warning;
1409 else
1410    raise;
1411 end if;
1412 
1413 END SET_PAYE_AGGR;
1414 
1415 
1416 --
1417 /* Name: get_paye_agg_status
1418    Details: This function is called from PERGBOBJ.fmb, for POST-INSERT event of secondary Assignment.
1419    Return: This will return the Error Message Name and Application, if any validations for PAYE Agg
1420            failed. Else it will return null. Return values are used in PERGBOBJ.fmb to show appropriate
1421            warning message to user. */
1422 FUNCTION get_paye_agg_status(p_person_id IN NUMBER,
1423                           p_effective_date IN DATE,
1424                           p_assignment_id IN NUMBER,
1425                           p_payroll_id IN NUMBER) return varchar2
1426 is
1427 l_msg_name varchar2(100);
1428 l_msg_appl varchar2(100);
1429 l_proc varchar2(60) := 'PER_ASG_AGGR.GET_PAYE_AGG_STATUS';
1430 begin
1431  hr_utility.set_location(' Entering:'||l_proc, 1);
1432 
1433  PER_ASG_AGGR.SET_PAYE_AGGR(p_person_id, p_effective_date, p_assignment_id, p_payroll_id);
1434 
1435  if G_VALIDATION_FAILURE then
1436     hr_utility.set_location(l_proc, 2);
1437     hr_utility.get_message_details(l_msg_name, l_msg_appl);
1438     G_VALIDATION_FAILURE := false;
1439     return l_msg_appl||':'||l_msg_name;
1440  end if;
1441 
1442  hr_utility.set_location(l_proc, 3);
1443  return null;
1444 end get_paye_agg_status;
1445 
1446 
1447 
1448 
1449 /*Code changes for RTI Payroll Id Population Post DML Calls*/
1450  FUNCTION check_for_active_emp
1451     (p_person_id      IN per_all_people_f.person_id%TYPE
1452     ,p_effective_date IN date) RETURN number IS
1453     var number;
1454   BEGIN
1455     SELECT  1
1456     INTO    var
1457     FROM    per_all_people_f pap
1458            ,per_person_types ppt
1459     WHERE   p_effective_date BETWEEN pap.effective_start_date
1460                              AND     pap.effective_end_date
1461     AND     pap.person_id = p_person_id
1462     AND     ppt.system_person_type = 'EMP'
1463     AND     pap.person_type_id = ppt.person_type_id;
1464 
1465 
1466     RETURN var;
1467   EXCEPTION
1468     WHEN no_data_found THEN
1469       var := 0;
1470 
1471 
1472       RETURN var;
1473   END check_for_active_emp;
1474 
1475   FUNCTION check_profile_exists
1476     (p_profile_name IN varchar2) RETURN boolean IS
1477     l_profile_value varchar2(30);
1478   BEGIN
1479     fnd_profile.get (p_profile_name
1480                     ,l_profile_value);
1481 
1482     IF l_profile_value = 'PARTIAL'
1483        OR l_profile_value = 'ALL' THEN
1484       RETURN TRUE;
1485     ELSE
1486       RETURN FALSE;
1487     END IF;
1488   END check_profile_exists;
1489 
1490   FUNCTION get_soy_date
1491     (p_effective_date IN date) RETURN date IS
1492     l_date_soy date;
1493   BEGIN
1494 
1495     IF p_effective_date
1496           >= to_date ('06-04-'
1497                       || substr (to_char (p_effective_date
1498                                          ,'YYYY/MON/DD')
1499                                 ,1
1500                                 ,4)
1501                      ,'DD-MM-YYYY') THEN
1502       l_date_soy := to_date ('06-04-'
1503                              || substr (to_char (p_effective_date
1504                                                 ,'YYYY/MON/DD')
1505                                        ,1
1506                                        ,4)
1507                             ,'DD-MM-YYYY');
1508 
1509       hr_utility.trace ('if part:'
1510                         || l_date_soy);
1511     ELSE
1512       l_date_soy := to_date ('06-04-'
1513                              || to_char (to_number (substr (to_char (p_effective_date
1514                                                                     ,'YYYY/MON/DD')
1515                                                            ,1
1516                                                            ,4)) - 1)
1517                             ,'DD-MM-YYYY');
1518 
1519       hr_utility.trace ('else part:'
1520                         || l_date_soy);
1521     END IF;
1522 
1523     hr_utility.trace ('date after soy check:'
1524                       || l_date_soy);
1525     RETURN fnd_date.date_to_displaydate (l_date_soy);
1526   END get_soy_date;
1527 
1528   PROCEDURE get_extra_info_exists
1529     (p_assignment_id  IN per_all_assignments_f.assignment_id%type
1530     ,p_assignment_extra_info_id OUT NOCOPY number
1531     ,p_object_version_number    OUT NOCOPY number) IS
1532     l_number number;
1533   BEGIN
1534     SELECT  assignment_extra_info_id
1535            ,object_version_number
1536     INTO    p_assignment_extra_info_id
1537            ,p_object_version_number
1538     FROM    per_assignment_extra_info
1539     WHERE   assignment_id = p_assignment_id
1540     AND     aei_information_category = 'GB_RTI_AGGREGATION';
1541   EXCEPTION
1542     WHEN no_data_found THEN
1543       p_assignment_extra_info_id := - 1;
1544   END get_extra_info_exists;
1545 
1546   PROCEDURE get_extra_info_rti_flag_exists
1547     (p_assignment_id  IN per_all_assignments_f.assignment_id%type
1548     ,p_assignment_extra_info_id OUT NOCOPY number
1549     ,p_object_version_number    OUT NOCOPY number) IS
1550     l_number number;
1551   BEGIN
1552     SELECT  assignment_extra_info_id
1553            ,object_version_number
1554     INTO    p_assignment_extra_info_id
1555            ,p_object_version_number
1556     FROM    per_assignment_extra_info
1557     WHERE   assignment_id = p_assignment_id
1558     AND     aei_information_category = 'GB_RTI_ASG_DETAILS';
1559   EXCEPTION
1560     WHEN no_data_found THEN
1561       p_assignment_extra_info_id := - 1;
1562   END get_extra_info_rti_flag_exists;
1563 
1564 
1565    FUNCTION get_ni_reporting_flag
1566     (p_assignment_id  IN number
1567     ,p_effective_date IN date
1568     ,p_person_id  IN number
1569     ,p_paye_reference in varchar2) RETURN varchar2 IS
1570     v_per_ni_flag varchar2(2);
1571     v_per_agg_flag varchar2(2);
1572     v_primary_flag varchar2(2);
1573     l_ni_reporting_flag varchar2(2);
1574     l_assignment_id NUMBER;
1575 
1576    cursor csr_primary_exists is
1577    select paf.assignment_id
1578    from
1579    per_all_people_f pap,
1580    per_all_assignments_f paf
1581    where paf.person_id = pap.person_id
1582    and   paf.person_id = p_person_id
1583    and  p_effective_date between paf.effective_start_date and paf.effective_end_date
1584    and  p_effective_date between pap.effective_start_date and pap.effective_end_date
1585    and nvl(paf.primary_flag,'N')='Y';
1586 
1587    cursor csr_primary_in_curr_paye is
1588    select paf.assignment_id
1589    from
1590    per_all_people_f pap,
1591    per_all_assignments_f paf,
1592    pay_all_payrolls_f pay,
1593    hr_soft_coding_keyflex hsc
1594    where paf.person_id = pap.person_id
1595    and   paf.assignment_id = p_assignment_id
1596    and   paf.payroll_id = pay.payroll_id
1597    and   pay.soft_coding_keyflex_id = hsc.soft_coding_keyflex_id
1598    and   hsc.segment1 = p_paye_reference
1599    and   p_effective_date between paf.effective_start_date and paf.effective_end_date
1600    and   p_effective_date between pap.effective_start_date and pap.effective_end_date
1601    and   nvl(paf.primary_flag,'N')='Y';
1602 
1603    -- find minimum assignment
1604    cursor csr_oldest_asg is
1605    select min(paf.assignment_id) from
1606    per_all_assignments_f paf,
1607    pay_all_payrolls_f pay,
1608    hr_soft_coding_keyflex hsc
1609    where paf.payroll_id= pay.payroll_id
1610    and   pay.soft_coding_keyflex_id= hsc.soft_coding_keyflex_id
1611    and   p_effective_date between pay.effective_start_date and pay.effective_end_date
1612    and   p_effective_date between paf.effective_start_date and paf.effective_end_date
1613    and   paf.person_id = p_person_id
1614    and   hsc.segment1= p_paye_reference;
1615 
1616 
1617 
1618   BEGIN
1619   hr_utility.trace('inside get_ni_reporting_flag for assignment:'||p_assignment_id);
1620     SELECT  trim (pap.per_information10) per_agg_flag
1621            ,trim (pap.per_information9) per_ni_flag
1622            ,nvl (paf.primary_flag
1623                 ,'N') primary_flag
1624     INTO    v_per_agg_flag
1625            ,v_per_ni_flag
1626            ,v_primary_flag
1627     FROM    per_all_people_f pap
1628            ,per_all_assignments_f paf
1629     WHERE   paf.person_id = pap.person_id
1630     AND     paf.assignment_id = p_assignment_id
1631     AND     p_effective_date BETWEEN paf.effective_start_date
1632                              AND     paf.effective_end_date
1633     AND     p_effective_date BETWEEN pap.effective_start_date
1634                              AND     pap.effective_end_date;
1635 
1636     IF nvl (v_per_agg_flag
1637            ,'N') = 'N'
1638        AND nvl (v_per_ni_flag
1639                ,'N') = 'Y'  then
1640         --AND nvl (v_primary_flag
1641                --,'N') = 'Y' THEN
1642        open csr_primary_exists;
1643           fetch csr_primary_exists into l_assignment_id;
1644 
1645           if csr_primary_exists%notfound then
1646             l_ni_reporting_flag:= null;
1647                hr_utility.trace('csr_primary_exists%notfound');
1648           else-- primary flag exists
1649             open csr_primary_in_curr_paye;
1650                fetch csr_primary_in_curr_paye into l_assignment_id;-- check for primary flag in current paye reference
1651                 if csr_primary_in_curr_paye%notfound then
1652                 hr_utility.trace('csr_primary_exists%notfound');
1653                        open csr_oldest_asg;
1654                             fetch csr_oldest_asg into l_assignment_id;
1655                       close csr_oldest_asg;
1656                end if;
1657               close csr_primary_in_curr_paye;
1658           end if;
1659          close csr_primary_exists;
1660   hr_utility.trace('get_ni_reporting_flag for assignment: l_assignment_id'||l_assignment_id);
1661       if l_assignment_id is not null then
1662            if l_assignment_id=p_assignment_id then
1663              l_ni_reporting_flag:='Y';
1664                hr_utility.trace('if part');
1665            else
1666                hr_utility.trace('else part');
1667              l_ni_reporting_flag:='N';
1668           end if;
1669 
1670       end if;
1671    else
1672     l_ni_reporting_flag:='N';
1673     END IF;
1674   hr_utility.trace('leaving get_ni_reporting_flag for assignment:'||l_ni_reporting_flag);
1675   hr_utility.trace('leaving get_ni_reporting_flag for assignment:'||p_assignment_id);
1676     RETURN l_ni_reporting_flag;
1677   END get_ni_reporting_flag;
1678 
1679   FUNCTION get_rti_payroll_id
1680     (p_person_id        IN per_all_people_f.person_id%TYPE
1681     ,p_assignment_id  IN per_all_assignments_f.assignment_id%type
1682     ,p_aggregation_flag IN varchar2
1683     ,p_effective_date   IN date) RETURN varchar2 IS
1684     v_rti_payroll_id varchar2(30);
1685     v_rti_assignment_id varchar2(30);
1686     v_check_data varchar2(10);
1687   BEGIN
1688     IF nvl (p_aggregation_flag
1689            ,'N') = 'Y' THEN
1690       SELECT  assignment_number
1691       INTO    v_rti_payroll_id
1692       FROM    per_all_assignments_f
1693       WHERE   person_id = p_person_id
1694       AND     nvl (primary_flag
1695                   ,'N') = 'Y'
1696       AND     p_effective_date BETWEEN effective_start_date
1697                                AND     effective_end_date;
1698     ELSE
1699       SELECT  assignment_number
1700       INTO    v_rti_payroll_id
1701       FROM    per_all_assignments_f
1702       WHERE   assignment_id = p_assignment_id
1703       AND     p_effective_date BETWEEN effective_start_date
1704                                AND     effective_end_date;
1705     END IF;
1706 
1707     RETURN v_rti_payroll_id;
1708   END get_rti_payroll_id;
1709 
1710   PROCEDURE update_rti_agg_update_asg
1711     (p_assignment_id  IN per_all_assignments_f.assignment_id%type
1712     ,p_effective_date IN date) IS
1713     p_person_id number;
1714   BEGIN
1715     SELECT  DISTINCT
1716             person_id
1717     INTO    p_person_id
1718     FROM    per_all_assignments_f
1719     WHERE   assignment_id = p_assignment_id
1720     AND     p_effective_date BETWEEN effective_start_date
1721                              AND     effective_end_date;
1722 
1723     per_asg_aggr.update_rti_agg_person (p_person_id
1724                                          ,p_effective_date);
1725 
1726   END update_rti_agg_update_asg;
1727 
1728   PROCEDURE update_rti_agg_new_person
1729     (p_person_id IN per_all_people_f.person_id%TYPE
1730     ,p_hire_date IN date) IS
1731   BEGIN
1732     per_asg_aggr.update_rti_agg_person
1733                      (p_person_id      => p_person_id
1734                      ,p_effective_date => p_hire_date);
1735   END update_rti_agg_new_person;
1736 
1737   PROCEDURE update_rti_agg_person
1738     (p_person_id      IN per_all_people_f.person_id%TYPE
1739     ,p_effective_date IN date) IS
1740     CURSOR csr_ni_paye_flag IS
1741       SELECT  trim (pap.per_information10) per_agg_flag
1742              ,trim (pap.per_information9) per_ni_flag
1743       FROM    per_all_people_f pap
1744       WHERE   pap.person_id = p_person_id
1745       AND     p_effective_date BETWEEN pap.effective_start_date
1746                                AND     pap.effective_end_date;
1747 
1748 							   /*15850011 Cursor Modified*/
1749     CURSOR csr_current_person_details IS
1750       SELECT  trim (paf.primary_flag) asg_primary_flag
1751              ,trim (pap.per_information10) per_agg_flag
1752              ,trim (pap.per_information9) per_ni_flag
1753              ,paf.assignment_id assignment_id
1754              ,paf.assignment_number assignment_number
1755              ,paf.effective_start_date assignment_start_date
1756              ,pap.business_group_id business_group_id
1757 			 ,nvl(
1758                  (SELECT MIN(paaf2.assignment_number)
1759                 FROM   per_all_assignments_f paaf2,
1760                        pay_all_payrolls_f papf1,
1761                        hr_soft_coding_keyflex hsck1
1762                 WHERE  paaf2.person_id                = paf.person_id
1763                 AND    papf1.payroll_id                = paaf2.payroll_id
1764                 AND    papf1.soft_coding_keyflex_id    = hsck1.soft_coding_keyflex_id
1765                 AND    hsck1.SEGMENT1                  = (hsck.segment1)
1766                 AND    paaf2.assignment_type          = 'E'
1767                 AND    paaf2.primary_flag             = 'Y'
1768                 AND   paf.effective_start_date BETWEEN paaf2.effective_start_date
1769                                                     AND paaf2.effective_end_date)
1770                   ,
1771                 (SELECT MIN(paaf2.assignment_number)
1772                 FROM   per_all_assignments_f paaf2,
1773                        pay_all_payrolls_f papf1,
1774                        hr_soft_coding_keyflex hsck1
1775                 WHERE  paaf2.person_id                = paf.person_id
1776                 AND    papf1.payroll_id                = paaf2.payroll_id
1777                 AND    papf1.soft_coding_keyflex_id     = hsck1.soft_coding_keyflex_id
1778                 AND    hsck1.SEGMENT1                  = (hsck.segment1)
1779                 AND    paaf2.assignment_type          = 'E'
1780                 AND    paf.effective_start_date BETWEEN paaf2.effective_start_date
1781                                                     AND paaf2.effective_end_date)
1782              ) primary_assignment_number
1783 			 ,hsck.segment1 paye_reference
1784       FROM    per_all_people_f pap
1785              ,per_all_assignments_f paf
1786 			 ,pay_all_payrolls_f papf
1787 			 ,hr_soft_coding_keyflex hsck
1788       WHERE   paf.person_id = pap.person_id
1789       AND     pap.person_id = p_person_id
1790 	  AND     papf.payroll_id=paf.payroll_id
1791 	  AND     papf.soft_coding_keyflex_id = hsck.soft_coding_keyflex_id
1792 	  AND     paf.assignment_type  = 'E'
1793       AND     pap.effective_start_date =
1794               (
1795                  SELECT MAX(papf2.effective_start_date)
1796                  FROM   per_all_people_f papf2
1797                  WHERE  papf2.person_id = pap.person_id
1798               )
1799       AND     paf.effective_start_date =
1800               (
1801                  SELECT MAX(paaf2.effective_start_date)
1802                  FROM   per_all_assignments_f paaf2
1803                  WHERE  paaf2.assignment_id         = paf.assignment_id
1804                  AND    paaf2.assignment_type       = 'E'
1805               )
1806       AND     TRUNC(sysdate) BETWEEN papf.effective_start_date
1807                                  AND papf.effective_end_date;
1808 
1809   cursor get_asg
1810   is
1811   select paaf.assignment_id
1812          ,paaf.assignment_number
1813          ,paaf.business_group_id
1814          ,trim (papf.per_information9)
1815   from per_all_assignments_f paaf
1816        ,per_all_people_f papf
1817   where paaf.person_id = p_person_id
1818   and papf.person_id = paaf.person_id
1819   AND p_effective_date BETWEEN paaf.effective_start_date
1820           AND paaf.effective_end_date
1821   AND p_effective_date BETWEEN papf.effective_start_date
1822           AND papf.effective_end_date;
1823 
1824     v_person_details csr_current_person_details%ROWTYPE;
1825     v_person_flags csr_ni_paye_flag%ROWTYPE;
1826     p_object_version_number number;
1827     l_assignment_number varchar2(30);
1828     l_ni_reporting_flag varchar2(2);
1829     l_rti_payroll_id varchar2(30) := null;
1830     l_payroll_id number;
1831     p_assignment_extra_info_id number;
1832     p_effect_date date;
1833     l_asg_id number;
1834     l_bus_group number;
1835     l_ni_flag varchar2(10);
1836   BEGIN
1837 
1838 
1839     hr_utility.trace ('inside hook call new rti aggregation package');
1840 
1841     hr_utility.trace ('person_id:'
1842                       || p_person_id);
1843 
1844     hr_utility.trace ('p_effective_date:'
1845                       || p_effective_date);
1846 
1847     IF ((check_profile_exists ('GB RTI UPTAKE'))
1848        AND (check_for_active_emp (p_person_id
1849                                 ,p_effective_date) = 1)) THEN
1850       hr_utility.trace ('profile is active so inside extra entry');
1851 
1852       OPEN csr_ni_paye_flag;
1853 
1854       FETCH csr_ni_paye_flag
1855         INTO    v_person_flags;
1856 
1857       CLOSE csr_ni_paye_flag;
1858 
1859       FOR c_person_info IN csr_current_person_details LOOP
1860 
1861 
1862         /*l_rti_payroll_id := get_rti_payroll_id (p_person_id
1863                                                ,c_person_info.assignment_id
1864                                                ,v_person_flags.per_agg_flag
1865                                                ,p_effective_date);*/
1866 
1867       /*15850011 Primary assignment assignment number in case of PAYE aggregated assignments
1868 	   If primary assignment is not in the same PAYE reference then the olderst assignment
1869 	   present in currrent assignment's paye reference will be considered primary
1870 	  */
1871 
1872 	   if 	nvl(c_person_info.per_agg_flag,'N') ='Y' then
1873             l_rti_payroll_id:= c_person_info.primary_assignment_number;
1874 	   else
1875 	       l_rti_payroll_id:= c_person_info.assignment_number;
1876 	   end if;
1877 
1878         hr_utility.trace ('v_person_flags.per_agg_flag:'
1879                           || c_person_info.per_agg_flag);
1880 
1881         hr_utility.trace ('p_effective_date:'
1882                           || p_effective_date);
1883 
1884         l_ni_reporting_flag := get_ni_reporting_flag (c_person_info.assignment_id
1885                                                      ,p_effective_date,p_person_id,c_person_info.paye_reference );
1886 
1887         get_extra_info_exists (c_person_info.assignment_id
1888                               ,p_assignment_extra_info_id
1889                               ,p_object_version_number);
1890 
1891         hr_utility.trace ('p_assignment_extra_info_id:'
1892                           || p_assignment_extra_info_id);
1893 
1894         hr_utility.trace ('assignment_id:'
1895                           || c_person_info.assignment_id);
1896 
1897         p_effect_date := get_soy_date (fnd_date.date_to_displaydate (p_effective_date));
1898 
1899         hr_utility.trace ('p_effect_date:'
1900                           || p_effect_date);
1901 
1902         /*IF (p_effect_date <= c_person_info.assignment_start_date) THEN
1903           p_effect_date := c_person_info.assignment_start_date;
1904         END IF;*/
1905 
1906         hr_utility.trace (' after if loop p_effect_date:'
1907                           || p_effect_date);
1908 
1909         IF p_assignment_extra_info_id = - 1 THEN
1910           pay_gb_aei_api.pay_gb_ins_rti_agg_strt
1911                            (p_assignment_id            => c_person_info.assignment_id
1912                            ,p_business_group_id        => c_person_info.business_group_id
1913                            ,p_information_type         => 'GB_RTI_AGGREGATION'
1914                            ,p_aei_information_category => 'GB_RTI_AGGREGATION'
1915                            ,p_aei_information1         => l_ni_reporting_flag
1916                            ,p_aei_information2         => fnd_date.date_to_canonical (p_effect_date)
1917                            ,p_aei_information3         => REGEXP_REPLACE(l_rti_payroll_id,'[]\#^}{_.@\[\$]','') --added for bug 16315781
1918                            ,p_aei_information4         => l_payroll_id
1919                            ,p_object_version_number    => p_object_version_number
1920                            ,p_assignment_extra_info_id => p_assignment_extra_info_id);
1921         ELSE
1922           pay_gb_aei_api.pay_gb_upd_rti_agg_strt
1923                            (p_assignment_extra_info_id => p_assignment_extra_info_id
1924                            ,p_business_group_id        => c_person_info.business_group_id
1925                            ,p_object_version_number    => p_object_version_number
1926                            ,p_aei_information_category => 'GB_RTI_AGGREGATION'
1927                            ,p_aei_information1         => l_ni_reporting_flag
1928                            ,p_aei_information2         => fnd_date.date_to_canonical (p_effect_date)
1929                            ,p_aei_information3         => REGEXP_REPLACE(l_rti_payroll_id,'[]\#^}{_.@\[\$]','') --added for bug 16315781
1930                            ,p_aei_information4         => l_payroll_id);
1931         END IF;
1932       END LOOP;
1933 	  --added for bug 16315781
1934     ---********** This special code is to trigger for Enter and Maintain template. ********************
1935       if l_rti_payroll_id is null then
1936 
1937         hr_utility.trace ('RTI Payroll id null. This is entering through templates.');
1938          open get_asg;
1939          fetch get_asg into l_asg_id, l_rti_payroll_id,l_bus_group,l_ni_flag;
1940          close get_asg;
1941          if l_asg_id is not null then
1942             get_extra_info_exists (l_asg_id
1943                               ,p_assignment_extra_info_id
1944                               ,p_object_version_number);
1945         hr_utility.trace ('p_assignment_extra_info_id:'
1946                           || p_assignment_extra_info_id);
1947         p_effect_date := get_soy_date (fnd_date.date_to_displaydate (p_effective_date));
1948         hr_utility.trace ('p_effect_date:'
1949                           || p_effect_date);
1950 
1951        IF p_assignment_extra_info_id = - 1 THEN
1952           pay_gb_aei_api.pay_gb_ins_rti_agg_strt
1953                            (p_assignment_id            => l_asg_id
1954                            ,p_business_group_id        => l_bus_group
1955                            ,p_information_type         => 'GB_RTI_AGGREGATION'
1956                            ,p_aei_information_category => 'GB_RTI_AGGREGATION'
1957                            ,p_aei_information1         => l_ni_flag
1958                            ,p_aei_information2         => fnd_date.date_to_canonical (p_effect_date)
1959                            ,p_aei_information3         => REGEXP_REPLACE(l_rti_payroll_id,'[]\#^}{_.@\[\$]','')
1960                            ,p_aei_information4         => l_payroll_id
1961                            ,p_object_version_number    => p_object_version_number
1962                            ,p_assignment_extra_info_id => p_assignment_extra_info_id);
1963         ELSE
1964           pay_gb_aei_api.pay_gb_upd_rti_agg_strt
1965                            (p_assignment_extra_info_id => p_assignment_extra_info_id
1966                            ,p_business_group_id        => l_bus_group
1967                            ,p_object_version_number    => p_object_version_number
1968                            ,p_aei_information_category => 'GB_RTI_AGGREGATION'
1969                            ,p_aei_information1         => l_ni_flag
1970                            ,p_aei_information2         => fnd_date.date_to_canonical (p_effect_date)
1971                            ,p_aei_information3         => REGEXP_REPLACE(l_rti_payroll_id,'[]\#^}{_.@\[\$]','')
1972                            ,p_aei_information4         => l_payroll_id);
1973         END IF;
1974 
1975        end if; --if l_asg_id is not null
1976 
1977       end if; --l_rti_payroll_id is null
1978 
1979     END IF;
1980   EXCEPTION
1981     WHEN others THEN
1982       hr_utility.trace (sqlerrm);
1983 
1984       hr_utility.trace ('leaving update_rti_agg_person');
1985 
1986 
1987   END update_rti_agg_person;
1988 --
1989 procedure update_asg_rti_starter_flag(p_person_id IN per_all_people_f.person_id%TYPE,
1990 p_effective_date IN DATE)
1991 is
1992 
1993 	CURSOR csr_get_all_asg(p_business_group_id NUMBER)
1994 	is
1995 	select paaf.assignment_id assignment_id
1996 	,sck.segment1 paye_ref
1997 	from per_all_assignments_f paaf,
1998 	pay_all_payrolls_f papf,
1999 	hr_soft_coding_keyflex sck
2000 	where paaf.person_id = p_person_id
2001 	and paaf.payroll_id = papf.payroll_id
2002 	and paaf.business_group_id = p_business_group_id
2003 	and papf.soft_coding_keyflex_id = sck.soft_coding_keyflex_id
2004 	and p_effective_date between papf.effective_start_date and papf.effective_end_date
2005 	and paaf.effective_start_date =
2006        ( select max(asg2.effective_start_date)
2007          from   per_all_assignments_f asg2
2008          where  asg2.assignment_id         = paaf.assignment_id
2009          and    asg2.assignment_type       = 'E'
2010          and    asg2.effective_start_date <= p_effective_date
2011        );
2012 
2013 	CURSOR csr_per_agg_flag
2014 	is
2015 	select per_information10 per_agg_flag
2016 	,business_group_id business_group_id
2017 	from per_all_people_f
2018 	where person_id = p_person_id
2019 	and p_effective_date between effective_start_date and effective_end_date;
2020 
2021 	--Fetches the assignment_id of the person within the same paye_ref
2022 	CURSOR csr_get_agg_asg(p_assignment_id NUMBER, p_paye_ref varchar2,p_business_group_id NUMBER)
2023 	is
2024 	select paaf.assignment_id assignment_id
2025 	from per_all_assignments_f paaf,
2026 	pay_all_payrolls_f papf,
2027 	hr_soft_coding_keyflex sck
2028 	where paaf.person_id = p_person_id
2029 	and paaf.assignment_id <> p_assignment_id
2030 	and paaf.business_group_id = p_business_group_id
2031 	and paaf.payroll_id = papf.payroll_id
2032 	and papf.soft_coding_keyflex_id = sck.soft_coding_keyflex_id
2033 	and upper(sck.segment1) = upper(p_paye_ref)
2034 	and p_effective_date between papf.effective_start_date and papf.effective_end_date
2035 	and paaf.effective_start_date =
2036        ( select max(asg2.effective_start_date)
2037          from   per_all_assignments_f asg2
2038          where  asg2.assignment_id         = paaf.assignment_id
2039          and    asg2.assignment_type       = 'E'
2040          and    asg2.effective_start_date <= p_effective_date
2041        );
2042 
2043 	--Fetches the RTI flags for other assignments of the person within the same paye_ref
2044 	CURSOR csr_starter_flags(c_assignment_id IN NUMBER)
2045 	is
2046 	select assignment_extra_info_id aeid
2047 	,aei_information8 starter_flag
2048 	,aei_information9 pensioner_flag
2049 	,aei_information19 expat_flag
2050 	,object_version_number
2051     FROM per_assignment_extra_info
2052     WHERE assignment_id  = c_assignment_id
2053     AND information_type = 'GB_RTI_ASG_DETAILS';
2054 
2055 	--Cursor to check whether the starter_flag is set by a EAS or FPS run.
2056 	cursor check_processed(p_assignment_id number,l_business_group_id number)
2057 	is
2058 	select 'Y' from dual
2059 	where exists (select *
2060 	from pay_payroll_actions ppa,
2061 	pay_assignment_actions paa
2062 	where ppa.report_type in ('RTI_EAS_REP','RTI_EAS_REP_13','RTI_FPS_REP','RTI_FPS_REP_13')
2063 	and ppa.action_status = 'C'
2064 	and ppa.business_group_id = l_business_group_id
2065 	and ppa.payroll_action_id = paa.payroll_action_id
2066 	and paa.assignment_id = p_assignment_id
2067   and paa.action_status = 'C');
2068 
2069 	v_starter_flags csr_starter_flags%rowtype;
2070 	v_flags_others csr_starter_flags%rowtype;
2071 	v_get_agg_asg csr_get_agg_asg%rowtype;
2072 	l_proc CONSTANT VARCHAR2(40) := 'update_asg_rti_starter_flag';
2073 	--l_person_id number;
2074 	l_paye_ref hr_organization_information.org_information1%TYPE;
2075     l_business_group_id number;
2076 	l_assignment_id number;
2077 	l_per_agg_flag VARCHAR2(1) := 'N';
2078 	l_update_rti_starter_flag VARCHAR2(1) := 'N';
2079     l_assignment_extra_info_id number;
2080 	l_object_version_number number;
2081 	l_ovn number;
2082   l_aeid number;
2083 	l_starter_flag varchar2(1) :='N';
2084 	l_pensioner_flag varchar2(1) :='N';
2085 	l_expat_flag varchar2(1) :='N';
2086   l_processed_flag varchar2(1) :='N';
2087 
2088 BEGIN
2089   --hr_utility.trace_on(null,'test');
2090 	hr_utility.set_location('Entering :'||l_proc,10);
2091     hr_utility.set_location('Person_id :'||p_person_id,20);
2092 	hr_utility.set_location('Effective_date :'||p_effective_date,30);
2093 
2094  IF ((check_profile_exists ('GB RTI UPTAKE'))
2095        AND (check_for_active_emp (p_person_id
2096                                 ,p_effective_date) = 1)) THEN
2097   	hr_utility.trace ('profile is active so inside extra entry');
2098 
2099   	open csr_per_agg_flag;
2100 		fetch csr_per_agg_flag into l_per_agg_flag , l_business_group_id;
2101 		close csr_per_agg_flag;
2102 
2103 		hr_utility.set_location('PAYE aggregated flag :'||l_per_agg_flag,40);
2104 		hr_utility.set_location('Business group id :'||l_business_group_id,50);
2105 
2106 		IF (nvl(l_per_agg_flag,'N') = 'Y') THEN
2107 
2108 			for l_asg_rec in csr_get_all_asg(l_business_group_id)
2109 			loop
2110 				hr_utility.set_location('Assignment_id :'||l_asg_rec.assignment_id,60);
2111 				hr_utility.set_location('Employers PAYE Ref :'||l_asg_rec.paye_ref,50);
2112 					l_starter_flag  :='N';
2113 					l_pensioner_flag  :='N';
2114 					l_expat_flag  :='N';
2115 
2116 				open csr_starter_flags(l_asg_rec.assignment_id);
2117 				fetch csr_starter_flags into l_aeid,l_starter_flag,l_pensioner_flag,l_expat_flag,l_ovn;
2118 				close csr_starter_flags;
2119 
2120 				hr_utility.trace('starter_flag :'||l_starter_flag);
2121 				hr_utility.trace('pensioner_flag :'||l_pensioner_flag);
2122 				hr_utility.trace('expat_flag :'||l_expat_flag);
2123 				IF (l_starter_flag <> 'Y' and
2124 				  l_pensioner_flag <> 'Y' and
2125 				  l_expat_flag <> 'Y') THEN
2126 
2127         	hr_utility.trace('inside inner loop');
2128 					open csr_get_agg_asg(l_asg_rec.assignment_id,l_asg_rec.paye_ref,l_business_group_id);
2129 					loop
2130 						fetch csr_get_agg_asg into v_get_agg_asg;
2131 						exit when csr_get_agg_asg%notfound;
2132 
2133 						open csr_starter_flags(v_get_agg_asg.assignment_id);
2134 						fetch csr_starter_flags into v_flags_others;
2135 						close csr_starter_flags;
2136 
2137 						IF (nvl(v_flags_others.starter_flag,'N') = 'Y' OR
2138 							nvl(v_flags_others.pensioner_flag,'N') = 'Y' OR
2139 							nvl(v_flags_others.expat_flag,'N') = 'Y') THEN
2140 
2141 								hr_utility.set_location('RTI flags found to be set for some assignment in the same PAYE Ref:',70);
2142 								l_update_rti_starter_flag := 'Y';
2143 								exit;
2144 						END IF;
2145 					 end loop;
2146 					close csr_get_agg_asg;
2147 
2148 					hr_utility.set_location('l_update_rti_starter_flag :'||l_update_rti_starter_flag,80);
2149 
2150 					IF l_update_rti_starter_flag = 'Y' THEN
2151 
2152 						hr_utility.set_location(' Setting the RTI_starter flag for p_assignment_id :'||l_asg_rec.assignment_id,90);
2153 
2154 						get_extra_info_rti_flag_exists (l_asg_rec.assignment_id
2155                               ,l_assignment_extra_info_id
2156                               ,l_object_version_number);
2157 
2158 						hr_utility.trace('Assignment extra info id  : '||l_assignment_extra_info_id);
2159 
2160 					IF l_assignment_extra_info_id = - 1 THEN
2161 						--set the rti sent flag for l_asg_rec.assignment_id
2162 						hr_assignment_extra_info_api.create_assignment_extra_info
2163 						(p_validate                       => false,
2164 						 p_assignment_id                  => l_asg_rec.assignment_id,
2165 						 p_information_type               => 'GB_RTI_ASG_DETAILS',
2166 						 p_aei_information_category       => 'GB_RTI_ASG_DETAILS',
2167 						 p_aei_information8               => 'Y',
2168 						 p_aei_information9               => 'N',
2169 						 p_aei_information19              => 'N',
2170 						 p_object_version_number          => l_object_version_number,
2171 						 p_assignment_extra_info_id       => l_assignment_extra_info_id
2172 						);
2173 
2174 						hr_utility.trace('New Assignment extra info id  : '||l_assignment_extra_info_id);
2175 					ELSE
2176 						--update the rti sent flag for p_assignment_id
2177 						hr_assignment_extra_info_api.update_assignment_extra_info
2178 						(p_validate                       => false,
2179 						 p_object_version_number          => l_object_version_number,
2180 						 p_assignment_extra_info_id       => l_assignment_extra_info_id,
2181 						 p_aei_information_category       => 'GB_RTI_ASG_DETAILS',
2182 						 p_aei_information8               => 'Y'
2183 						);
2184 
2185 						hr_utility.trace('Existing Assignment extra info id  : '||l_assignment_extra_info_id);
2186 					END IF;
2187 
2188 				END IF;
2189 			END IF;
2190 		END LOOP;
2191 
2192 		ELSE -- if aggegation changed from PAYE to Non-aggregated
2193 
2194 		for l_asg_rec in csr_get_all_asg(l_business_group_id)
2195 			loop
2196 				hr_utility.set_location('Assignment_id :'||l_asg_rec.assignment_id,95);
2197 				l_starter_flag := 'N';
2198 				l_pensioner_flag := 'N';
2199 				l_expat_flag := 'N';
2200 
2201 				open csr_starter_flags(l_asg_rec.assignment_id);
2202 				fetch csr_starter_flags into l_aeid,l_starter_flag,l_pensioner_flag,l_expat_flag,l_ovn;
2203 				close csr_starter_flags;
2204 
2205 				l_processed_flag := 'N';
2206 				open check_processed(l_asg_rec.assignment_id,l_business_group_id);
2207 				fetch check_processed into l_processed_flag;
2208 				close check_processed;
2209 
2210 				IF (l_starter_flag = 'Y' AND nvl(l_processed_flag,'N') <> 'Y') then
2211 				--starter flag set during assignment creation when PAYE_aggregated
2212 					hr_utility.set_location(' re-setting the RTI_starter flag for p_assignment_id :'||l_asg_rec.assignment_id,90);
2213 					get_extra_info_rti_flag_exists (l_asg_rec.assignment_id
2214                               ,l_assignment_extra_info_id
2215                               ,l_object_version_number);
2216 
2217 					hr_utility.trace('Assignment extra info id  : '||l_assignment_extra_info_id);
2218 					IF l_assignment_extra_info_id <> - 1 THEN
2219 					--update the rti sent flag for p_assignment_id
2220 						hr_assignment_extra_info_api.update_assignment_extra_info
2221 						(p_validate                       => false,
2222 						 p_object_version_number          => l_object_version_number,
2223 						 p_assignment_extra_info_id       => l_assignment_extra_info_id,
2224 						 p_aei_information_category       => 'GB_RTI_ASG_DETAILS',
2225 						 p_aei_information8               => 'N'
2226 						);
2227 
2228 						hr_utility.trace('Existing Assignment extra info id  : '||l_assignment_extra_info_id);
2229 					  END IF;
2230 					END IF;
2231 				end loop;
2232 		END IF;
2233 END IF;
2234 	hr_utility.set_location('Leaving :'||l_proc,100);
2235 --  hr_utility.trace_off;
2236 EXCEPTION
2237 	when others then
2238 	 hr_utility.trace (sqlerrm);
2239 
2240    hr_utility.set_location('Leaving :'||l_proc,999);
2241 
2242 END update_asg_rti_starter_flag;
2243 --
2244   PROCEDURE update_rti_starter_asg
2245     (p_assignment_id  IN per_all_assignments_f.assignment_id%type
2246     ,p_effective_date IN date) IS
2247     p_person_id number;
2248   BEGIN
2249     SELECT  DISTINCT
2250             person_id
2251     INTO    p_person_id
2252     FROM    per_all_assignments_f
2253     WHERE   assignment_id = p_assignment_id
2254     AND     p_effective_date BETWEEN effective_start_date
2255                              AND     effective_end_date;
2256 
2257     per_asg_aggr.update_asg_rti_starter_flag (p_person_id
2258                                          ,p_effective_date);
2259 
2260   END update_rti_starter_asg;
2261 --
2262 
2263 
2264 END per_asg_aggr;
2265