DBA Data[Home] [Help]

PACKAGE BODY: APPS.PAY_AU_PAYMENT_SUMMARY_REPORT

Source


4 *** ------------------------------------------------------------------------+
1 package body pay_au_payment_summary_report as
2 /* $Header: pyaupsrp.pkb 120.9.12020000.2 2013/02/04 05:47:10 skshin ship $*/
3 /*
5 *** Program:     pay_au_payment_summary_report (Package Body)
6 ***
7 *** Change History
8 ***
9 *** Date       Changed By  Version  Description of Change
10 *** ---------  ----------  -------  ----------------------------------------+
11 *** 01 MAR 01  kaverma     1.0           Initial version
12 *** 28 Nov 01  nnaresh     1.1           Updated for GSCC Standards
13 *** 29 Nov 01  nnaresh     1.2           Replaced REM with ***
14 *** 03 DEC 02  Ragovind    1.7           Added NOCOPY for the function range_code.
15 *** 18 FEB 03  nanuradh    1.8  2786549  Removed number_of_copies parameter when setting
16 ***                                      printer options
17 *** 25 FEB 03  nanuradh    1.9  2786549  Removed the fix done for the bug #2786549
18 *** 29 MAY 03  apunekar    1.10 2920725  Corrected base tables to support security model
19 *** 17 NOV 03  avenkatk    1.11 3132172  Added support for printing report on
20 ***                                      duplex printers.
21 *** 10 FEB 04  punmehta    1.12 3098353  Added check for archive flag
22 *** 21 JUL 04  srrajago    1.13 3768288  Modified cursor 'csr_get_print_options' to fetch value 'number_of_copies'
23 ***                                      and the same is passed to fnd_request.set_print_options.Resolved GSCC warning in
24 ***                                      assigning value -1 to ps_request_id.
25 *** 09 AUG 04  abhkumar    1.14 2610141  Legal Employer Enhancement
26 *** 09 DEC 04  ksingla     1.15 3937976  Added check for archive flag X_CURR_TERM_0_BAL_FLAG
27 *** 06 DEC 05  avenkatk    1.16 4859876  Added support for XML Publisher PDF Template
28 *** 02 JAN 06  avenkatk    1.17 4891196  Added support for PDF and Postscript generation of report.
29 *** 03 Jan 06  abhargav    1.18 4726357  Added function to get the self serivce option.
30 *** 28_feb-07  abhargav    1.20 5743270  Added check so that empty self printed report will not be generated
31 ***                                      for cases where for all the assignment Self Printed flag is set 'Yes'.
32 *** 09-Jan-08  avenkatk    115.21 6470581  Added Changes for Amended Payment Summary
33 *** 23-Jan-08  avenkatk    115.22 6470581  Resolved GSCC Errors
34 *** 26 May 09  avenkatk    115.23 8501365  Added RANGE_PERSON_ID for Self Printed Payment Summary
35 *** 11 Dec 09  dduvvuri    115.25 9113084  Added RANGE_PERSON_ID for Amended Self Printed Payment Summary
36 *** 16-Apr-10  avenkatk    115.26 9534762  Added ORDERED hint to Assignment Action Code cursor
37 *** 04-Feb-13  skshin      115.27 14621185  Added additional NOT EXIST condition to Amended Assignment Action Code cursors
38 *** ------------------------------------------------------------------------+
39 */
40 
41   g_debug       boolean;  /* Bug 6470581 */
42 
43   -------------------------------------------------------------------------
44   -- This procedure returns a sql string to select a range
45   -- of assignments eligible for archive report process.
46   -------------------------------------------------------------------------
47 
48   procedure range_code
49     (p_payroll_action_id   in pay_payroll_actions.payroll_action_id%type,
50      p_sql                 out NOCOPY varchar2) is
51   begin
52      hr_utility.set_location('Start of range_code',1);
53 
54     /*Bug2920725   Corrected base tables to support security model*/
55 
56       p_sql := ' select distinct p.person_id'                                     ||
57              ' from   per_people_f p,'                                        ||
58                     ' pay_payroll_actions pa'                                     ||
59              ' where  pa.payroll_action_id = :payroll_action_id'                  ||
60              ' and    p.business_group_id = pa.business_group_id'                 ||
61              ' order by p.person_id';
62 
63      hr_utility.set_location('End of range_code',2);
64   end range_code;
65 
66 
67 /*
68     Bug 8501365 - Added Function range_person_on
69 --------------------------------------------------------------------
70     Name  : range_person_on
71     Type  : Function
72     Access: Private
73     Description: Checks if RANGE_PERSON_ID is enabled for
74                  Archive process.
75   --------------------------------------------------------------------
76    Bug 9113084 - Check if Range Person is enabled for Self Printed Payment Summary
77 */
78 
79 FUNCTION range_person_on
80 RETURN BOOLEAN
81 IS
82 
83  CURSOR csr_action_parameter is
84   select parameter_value
85   from pay_action_parameters
86   where parameter_name = 'RANGE_PERSON_ID';
87 
88  CURSOR csr_range_format_param is
89   select par.parameter_value
90   from   pay_report_format_parameters par,
91          pay_report_format_mappings_f map
92   where  map.report_format_mapping_id = par.report_format_mapping_id
93   and    map.report_type = 'AU_PAYMENT_SUMMARY_REPORT'
94   and    map.report_format = 'AU_PAYMENT_SUMMARY_REPORT'
95   and    map.report_qualifier = 'AU'
96   and    par.parameter_name = 'RANGE_PERSON_ID';
97 
101 
98   l_return boolean;
99   l_action_param_val varchar2(30);
100   l_report_param_val varchar2(30);
102 BEGIN
103 
104     g_debug := hr_utility.debug_enabled;
105 
106   BEGIN
107 
108     open csr_action_parameter;
109     fetch csr_action_parameter into l_action_param_val;
110     close csr_action_parameter;
111 
112     open csr_range_format_param;
113     fetch csr_range_format_param into l_report_param_val;
114     close csr_range_format_param;
115 
116   EXCEPTION WHEN NO_DATA_FOUND THEN
117      l_return := FALSE;
118   END;
119   --
120   IF l_action_param_val = 'Y' AND l_report_param_val = 'Y' THEN
121      l_return := TRUE;
122      IF g_debug THEN
123          hr_utility.set_location('Range Person = True',1);
124      END IF;
125   ELSE
126      l_return := FALSE;
127   END IF;
128 --
129  RETURN l_return;
130 --
131 END range_person_on;
132 
133 
134  -------------------------------------------------------------------------
135   -- This procedure further restricts the assignment_id's
136   -- returned by range_code and locks the Assignment Actions for which
137   -- a Payment Summry Report has been printed.
138  -------------------------------------------------------------------------
139 
140 
141 -- this procedure filters the assignments selected by range_code procedure
142 -- it then calls hr_nonrun.insact to create an assignment  id
143 -- the cursor to select assignment action selects assignment id for which
144 -- archival has been done.
145 
146 procedure assignment_action_code
147       (p_payroll_action_id  in pay_payroll_actions.payroll_action_id%type,
148        p_start_person_id    in per_all_people_f.person_id%type,
149        p_end_person_id      in per_all_people_f.person_id%type,
150        p_chunk              in number) is
151 
152     v_next_action_id  pay_assignment_actions.assignment_action_id%type;
153 
154     /*Bug2920725   Corrected base tables to support security model*/
155 
156 
157       cursor process_assignments
158         (c_payroll_action_id  in pay_payroll_actions.payroll_action_id%type,
159          c_start_person_id    in per_all_people_f.person_id%type,
160          c_end_person_id      in per_all_people_f.person_id%type) is
161          select  distinct a.assignment_id,
162                  pay_core_utils.get_parameter('ARCHIVE_ID', pa.legislative_parameters) archive_action_id,
163                  ppac.assignment_action_id
164                 from   per_assignments_f a,
165                        per_people_f p,
166                        pay_payroll_actions pa,
167                        pay_payroll_actions ppa,
168                        pay_assignment_actions ppac
169                 where  pa.payroll_action_id   = c_payroll_action_id
170                  and    p.person_id             between c_start_person_id and c_end_person_id
171                  and    p.person_id           = a.person_id
172                  and    p.business_group_id   = pa.business_group_id
173                  and    ppa.payroll_action_id = ppac.payroll_action_id
174                  and    a.assignment_id       = ppac.assignment_id
175                  and    ppa.payroll_action_id = pay_core_utils.get_parameter('ARCHIVE_ID', pa.legislative_parameters)
176                  And    ppa.action_type       = 'X'
177                  and    ppa.action_status     = 'C'
178                  and    pay_au_payment_summary.get_archive_value('X_REPORTING_FLAG', ppac.assignment_action_id)='YES'   --3098353
179                  and    pay_au_payment_summary.get_archive_value('X_CURR_TERM_0_BAL_FLAG', ppac.assignment_action_id)='NO'   --3937976
180                  and  not exists
181                             (select locked_action_id
182                              FROM   pay_action_interlocks pail
183                            WHERE pail.locked_action_id=ppac.assignment_action_id)
184                  and ppac.assignment_action_id in
185                          (select max(ppac1.assignment_action_id)
186                           from pay_assignment_actions ppac1,
187                                pay_payroll_Actions    ppaa
188                           where ppaa.action_type       ='X'
189                            and  ppaa.action_status     ='C'
190                            and  pay_core_utils.get_parameter('REGISTERED_EMPLOYER', ppaa.legislative_parameters) =
191                                 pay_core_utils.get_parameter('REGISTERED_EMPLOYER', pa.legislative_parameters) --2610141
192                            and  ppaa.report_type       ='AU_PAYMENT_SUMMARY'
193                            and  ppaa.payroll_Action_id = ppac1.payroll_action_id
194                           group by ppac1.assignment_id);
195 
196 /*
197    Bug 8501365 - Added Cursor for Range Person
198                - Uses person_id in pay_population_ranges
199   --------------------------------------------------------------------+
200   -- Cursor      : range_process_assignments
201   -- Description : Fetches assignments For Payment Summary
202   --               Returns DISTINCT assignment_id
203   --               Used when RANGE_PERSON_ID feature is enabled
204   --------------------------------------------------------------------+
205 */
206 
207 
208 CURSOR range_process_assignments
209         (c_payroll_action_id  in pay_payroll_actions.payroll_action_id%type,
210          c_chunk              in NUMBER)
211 IS
212 SELECT  /*+ ORDERED */
213         DISTINCT a.assignment_id,
214         pay_core_utils.get_parameter('ARCHIVE_ID', pa.legislative_parameters) archive_action_id,
215         ppac.assignment_action_id
216 FROM    pay_payroll_actions pa,
217         pay_population_ranges ppr,
221         pay_assignment_actions ppac
218         pay_payroll_actions ppa,
219         per_people_f p,
220         per_assignments_f a,
222 WHERE  pa.payroll_action_id  = c_payroll_action_id
223 AND   ppr.payroll_action_id  = pa.payroll_action_id
224 AND   ppr.chunk_number       = c_chunk
225 AND   p.person_id            = ppr.person_id
226 AND   p.person_id            = a.person_id
227 AND   p.business_group_id    = pa.business_group_id
228 AND   ppa.payroll_action_id  = ppac.payroll_action_id
229 AND   a.assignment_id        = ppac.assignment_id
230 AND   ppa.payroll_action_id  = pay_core_utils.get_parameter('ARCHIVE_ID', pa.legislative_parameters)
231 AND   ppa.report_type        = 'AU_PAYMENT_SUMMARY'
232 AND   ppa.report_qualifier   = 'AU'
233 AND   ppa.report_category    = 'REPORT'
234 AND   ppa.action_type        = 'X'
235 AND   ppa.action_status      = 'C'
236 AND   pay_au_payment_summary.get_archive_value('X_REPORTING_FLAG', ppac.assignment_action_id)='YES'
237 AND   pay_au_payment_summary.get_archive_value('X_CURR_TERM_0_BAL_FLAG', ppac.assignment_action_id)='NO'
238 AND  NOT EXISTS
239            (SELECT locked_action_id
240             FROM   pay_action_interlocks pail
241             WHERE  pail.locked_action_id   = ppac.assignment_action_id)
242 AND ppac.assignment_action_id IN
243         (SELECT MAX(ppac1.assignment_action_id)
244          FROM pay_assignment_actions ppac1,
245               pay_payroll_Actions    ppaa
246          where ppaa.action_type       ='X'
247           AND  ppaa.action_status     ='C'
248           AND  pay_core_utils.get_parameter('REGISTERED_EMPLOYER', ppaa.legislative_parameters) =
249                pay_core_utils.get_parameter('REGISTERED_EMPLOYER', pa.legislative_parameters)
250           AND  ppaa.report_type       = 'AU_PAYMENT_SUMMARY'
251           AND  ppaa.report_qualifier  = 'AU'
252           AND  ppaa.report_category   = 'REPORT'
253           AND  ppac1.assignment_id    = ppac.assignment_id
254           AND  ppaa.payroll_Action_id = ppac1.payroll_action_id
255          GROUP BY ppac1.assignment_id);
256 
257 
258 
259   cursor next_action_id is
260         select pay_assignment_actions_s.nextval
261         from   dual;
262 
263 
264 /* Bug 6470581 - Added the Following cursors to get Payment Summary Information
265    and asignments eligible for Self Printed process for Amended PS
266 */
267 
268 CURSOR c_get_paysum_details
269         (c_payroll_action_id pay_payroll_actions.payroll_action_id%TYPE)
270 IS
271 SELECT to_number(pay_core_utils.get_parameter('REGISTERED_EMPLOYER', ppa.legislative_parameters)) registered_employer
272       ,pay_core_utils.get_parameter('ARCHIVE_ID', ppa.legislative_parameters)           archive_id
273       ,NVL(pay_core_utils.get_parameter('PAY_SUM_TYPE', ppa.legislative_parameters),'O')       payment_summary_type
274       ,pay_core_utils.get_parameter('FINANCIAL_YEAR', ppa.legislative_parameters)       fin_year
275 FROM pay_payroll_actions ppa
276 WHERE ppa.payroll_action_id = c_payroll_action_id;
277 
278 
279 CURSOR c_amend_process_assignments
280         (c_payroll_action_id  IN pay_payroll_actions.payroll_action_id%TYPE
281         ,c_start_person_id    IN per_all_people_f.person_id%TYPE
282         ,c_end_person_id      IN per_all_people_f.person_id%TYPE
283         ,c_archive_id         IN pay_payroll_actions.payroll_action_id%TYPE
284         ,c_reg_emp            IN pay_assignment_actions.tax_unit_id%TYPE
285         ,c_financial_year     VARCHAR2)
286 IS
287 SELECT  DISTINCT a.assignment_id
288         ,pay_core_utils.get_parameter('ARCHIVE_ID', pa.legislative_parameters) archive_action_id
289         ,ppac.assignment_action_id
290         ,pmaa.assignment_action_id datafile_action_id
291 FROM     per_assignments_f a
292         ,per_people_f p
293         ,pay_payroll_actions pa
294         ,pay_payroll_actions ppa
295         ,pay_assignment_actions ppac
296         ,pay_assignment_actions pmaa
297         ,pay_payroll_actions pmpa
298 WHERE  pa.payroll_action_id   = c_payroll_action_id
299 AND    p.person_id             between c_start_person_id and c_end_person_id
300 AND    p.person_id           = a.person_id
301 AND    p.business_group_id   = pa.business_group_id
302 AND    ppa.payroll_action_id = ppac.payroll_action_id
303 AND    a.assignment_id       = ppac.assignment_id
304 AND    ppa.payroll_action_id = c_archive_id
305 AND    ppa.action_type       = 'X'
306 AND    ppa.action_status     = 'C'
307 AND    pay_au_payment_summary.get_archive_value('X_REPORTING_FLAG', ppac.assignment_action_id)='YES'
308 AND    pay_au_payment_summary.get_archive_value('X_CURR_TERM_0_BAL_FLAG', ppac.assignment_action_id)='NO'
309 AND    pay_au_payment_summary.get_archive_value('X_PAYMENT_SUMMARY_TYPE', ppac.assignment_action_id)='A'   /* Indicates something has changed */
310 AND    pmaa.assignment_id    = ppac.assignment_id
311 AND    pmaa.payroll_action_id = pmpa.payroll_action_id
312 AND    pmpa.report_type       = 'AU_PS_DATA_FILE'
313 AND    pmpa.action_type       = 'X'
314 AND    pmpa.action_status     = 'C'
315 AND    pay_core_utils.get_parameter('REGISTERED_EMPLOYER', pmpa.legislative_parameters) = c_reg_emp
316 AND    pay_core_utils.get_parameter('FINANCIAL_YEAR', pmpa.legislative_parameters) = c_financial_year
317 AND  NOT EXISTS
318         (SELECT locked_action_id
319          FROM  pay_action_interlocks pail
320          WHERE pail.locked_action_id=ppac.assignment_action_id)
321 AND  NOT EXISTS /* bug 14621185 - restricting to return the latest archive only */
322         (SELECT locked_action_id
323          FROM  pay_action_interlocks pail
324          WHERE pail.locked_action_id=pmaa.assignment_action_id)
325 AND ppac.assignment_action_id IN
326                         (SELECT MAX(ppac1.assignment_action_id)
327                          FROM   pay_assignment_actions ppac1,
331                          AND   pay_core_utils.get_parameter('REGISTERED_EMPLOYER', ppaa.legislative_parameters) =
328                                 pay_payroll_Actions    ppaa
329                          WHERE ppaa.action_type       ='X'
330                          AND   ppaa.action_status     ='C'
332                                 pay_core_utils.get_parameter('REGISTERED_EMPLOYER', pa.legislative_parameters) --2610141
333                          AND  ppaa.report_type       ='AU_PAY_SUMM_AMEND'
334                          AND  ppaa.payroll_Action_id = ppac1.payroll_action_id
335                          GROUP BY ppac1.assignment_id);
336 
337 /* 9113084 - Added new cursor for above cursor c_amend_process_assignments */
338 /* 9113084 - Cursor to fetch assignments for Self Printed Amended Payment Summary when RANGE_PERSON_ID is enabled */
339 CURSOR rg_amend_process_assignments
340         (c_payroll_action_id  IN pay_payroll_actions.payroll_action_id%TYPE
341         ,c_chunk IN NUMBER
342         ,c_archive_id         IN pay_payroll_actions.payroll_action_id%TYPE
343         ,c_reg_emp            IN pay_assignment_actions.tax_unit_id%TYPE
344         ,c_financial_year     VARCHAR2)
345 IS
346 SELECT  DISTINCT a.assignment_id
347         ,pay_core_utils.get_parameter('ARCHIVE_ID', pa.legislative_parameters) archive_action_id
348         ,ppac.assignment_action_id
349         ,pmaa.assignment_action_id datafile_action_id
350 FROM     per_assignments_f a
351         ,per_people_f p
352         ,pay_payroll_actions pa
353         ,pay_payroll_actions ppa
354         ,pay_assignment_actions ppac
355         ,pay_assignment_actions pmaa
356         ,pay_payroll_actions pmpa
357     ,pay_population_ranges ppr
358 WHERE  pa.payroll_action_id   = c_payroll_action_id
359 AND    ppr.payroll_action_id = pa.payroll_action_id
360 AND    ppr.chunk_number = c_chunk
361 AND    p.person_id             = ppr.person_id
362 AND    p.person_id           = a.person_id
363 AND    p.business_group_id   = pa.business_group_id
364 AND    ppa.payroll_action_id = ppac.payroll_action_id
365 AND    a.assignment_id       = ppac.assignment_id
366 AND    ppa.payroll_action_id = c_archive_id
367 AND    ppa.action_type       = 'X'
368 AND    ppa.action_status     = 'C'
369 AND    pay_au_payment_summary.get_archive_value('X_REPORTING_FLAG', ppac.assignment_action_id)='YES'
370 AND    pay_au_payment_summary.get_archive_value('X_CURR_TERM_0_BAL_FLAG', ppac.assignment_action_id)='NO'
371 AND    pay_au_payment_summary.get_archive_value('X_PAYMENT_SUMMARY_TYPE', ppac.assignment_action_id)='A'
372 AND    pmaa.assignment_id    = ppac.assignment_id
373 AND    pmaa.payroll_action_id = pmpa.payroll_action_id
374 AND    pmpa.report_type       = 'AU_PS_DATA_FILE'
375 AND    pmpa.action_type       = 'X'
376 AND    pmpa.action_status     = 'C'
377 AND    pay_core_utils.get_parameter('REGISTERED_EMPLOYER', pmpa.legislative_parameters) = c_reg_emp
378 AND    pay_core_utils.get_parameter('FINANCIAL_YEAR', pmpa.legislative_parameters) = c_financial_year
379 AND  NOT EXISTS
380         (SELECT locked_action_id
381          FROM  pay_action_interlocks pail
382          WHERE pail.locked_action_id=ppac.assignment_action_id)
383 AND  NOT EXISTS /* bug 14621185 - restricting to return the latest archive only */
384         (SELECT locked_action_id
385          FROM  pay_action_interlocks pail
386          WHERE pail.locked_action_id=pmaa.assignment_action_id)
387 AND ppac.assignment_action_id IN
388                         (SELECT MAX(ppac1.assignment_action_id)
389                          FROM   pay_assignment_actions ppac1,
390                                 pay_payroll_Actions    ppaa
391                          WHERE ppaa.action_type       ='X'
392                          AND   ppaa.action_status     ='C'
393                          AND   pay_core_utils.get_parameter('REGISTERED_EMPLOYER', ppaa.legislative_parameters) =
394                                 pay_core_utils.get_parameter('REGISTERED_EMPLOYER', pa.legislative_parameters)
395                          AND  ppaa.report_type       ='AU_PAY_SUMM_AMEND'
396                          AND  ppaa.payroll_Action_id = ppac1.payroll_action_id
397                          GROUP BY ppac1.assignment_id);
398 
399 l_get_paysum_details c_get_paysum_details%ROWTYPE;
400 
401 /* End Bug 6470581 */
402 
403   BEGIN
404 
405   g_debug := hr_utility.debug_enabled;
406 
407         IF g_debug
408         THEN
409                hr_utility.set_location('Start of assignment_action_code',3);
410                hr_utility.set_location('The payroll_action_id passed  '|| p_payroll_action_id,4);
411                hr_utility.set_location('The p_start_person_id  '|| p_start_person_id,5);
412                hr_utility.set_location('The p_end_person_id '|| p_end_person_id,6);
413                hr_utility.set_location('The p_chunk number '|| p_chunk ,7);
414         END IF;
415 
416         /* Bug 6470581 - Fetch the Payment Summary Type details.
417                          If Type is 'O' (Original), lock only Archive action
418                          If Type is 'A' (Amended) , lock Archive and Original Data file actions
419         */
420 
421         OPEN c_get_paysum_details(p_payroll_action_id);
422         FETCH c_get_paysum_details INTO l_get_paysum_details;
423         CLOSE c_get_paysum_details;
424 
425 IF l_get_paysum_details.payment_summary_type = 'O'
426 THEN
427         /* Bug 8501365 - Added Changes for Range Person
428                        - Call Cursor using pay_population_ranges if Range Person Enabled
429             Else call Old Cursor
430          */
431         IF range_person_on
432         THEN
433 
434                FOR csr_rec IN range_process_assignments(p_payroll_action_id
435                                                        ,p_chunk)
436                 LOOP
437                         OPEN next_action_id;
441                                                csr_rec.assignment_id,
438                         FETCH next_action_id into v_next_action_id;
439                         CLOSE next_action_id;
440                         hr_nonrun_asact.insact(v_next_action_id,
442                                                p_payroll_action_id,
443                                                p_chunk,
444                                                null);
445                         hr_nonrun_asact.insint(v_next_action_id,csr_rec.assignment_action_id);
446                         IF g_debug
447                         THEN
448                                 hr_utility.set_location('Assignment_ID                  '||csr_rec.assignment_id,35);
449                                 hr_utility.set_location('New Ass Action ID              '||v_next_action_id,40);
450                                 hr_utility.set_location('Locked Archive Action ID       '||csr_rec.assignment_action_id,45);
451                         END IF;
452                 END LOOP;
453 
454         ELSE
455 
456            for process_rec in process_assignments (p_payroll_action_id,
457                                                    p_start_person_id,
458                                                    p_end_person_id)
459            loop
460             hr_utility.set_location('LOOP STARTED   '|| process_rec.assignment_id ,14);
461             open next_action_id;
462             fetch next_action_id into v_next_action_id;
463             close next_action_id;
464             hr_utility.set_location('before calling insact  '|| v_next_action_id ,14);
465             hr_nonrun_asact.insact(v_next_action_id,
466                                      process_rec.assignment_id,
467                                      p_payroll_action_id,
468                                      p_chunk,
469                                    null);
470             hr_utility.set_location('inserted assigment action assignment '|| process_rec.assignment_id ,15);
471             hr_utility.set_location('Before calling hr_nonrun_asact.insint archive ' || process_rec.archive_action_id,16);
472             hr_utility.set_location('v_next_action_id' || v_next_action_id,16);
473             hr_nonrun_asact.insint(v_next_action_id,process_rec.assignment_action_id);
474             hr_utility.set_location('After calling hr_nonrun_asact.insint',14);
475            end loop;
476            hr_utility.set_location('End of assignment_action_code',5);
477         END IF;
478 
479 ELSIF l_get_paysum_details.payment_summary_type = 'A'
480 THEN
481        IF range_person_on THEN /* 9113084 - Use new Range Person Cursor if Range Person is enabled */
482            IF g_debug THEN
483                 hr_utility.set_location('Using Range Person Cursor for fetching assignments',30);
484            END IF;
485        FOR csr_rec IN rg_amend_process_assignments(p_payroll_action_id
486                                                  ,p_chunk
487                                                  ,l_get_paysum_details.archive_id
488                                                  ,l_get_paysum_details.registered_employer
489                                                  ,l_get_paysum_details.fin_year)
490         LOOP
491 
492                 OPEN next_action_id;
493                 FETCH next_action_id into v_next_action_id;
494                 CLOSE next_action_id;
495                 hr_nonrun_asact.insact(v_next_action_id,
496                                 csr_rec.assignment_id,
497                                 p_payroll_action_id,
498                                 p_chunk,
499                                null);
500                 hr_nonrun_asact.insint(v_next_action_id,csr_rec.assignment_action_id);
501                 hr_nonrun_asact.insint(v_next_action_id,csr_rec.datafile_action_id);
502 
503                 IF g_debug
504                 THEN
505                         hr_utility.set_location('Assignment_ID                  '||csr_rec.assignment_id,35);
506                         hr_utility.set_location('New Ass Action ID              '||v_next_action_id,40);
507                         hr_utility.set_location('Locked Archive Action ID       '||csr_rec.assignment_action_id,45);
508                         hr_utility.set_location('Locked Data file Action ID     '||csr_rec.datafile_action_id,50);
509                 END IF;
510         END LOOP;
511        ELSE /* 9113084 - Use Old logic if Range Person is disabled */
512 
513        FOR csr_rec IN c_amend_process_assignments(p_payroll_action_id
514                                                  ,p_start_person_id
515                                                  ,p_end_person_id
516                                                  ,l_get_paysum_details.archive_id
517                                                  ,l_get_paysum_details.registered_employer
518                                                  ,l_get_paysum_details.fin_year)
519         LOOP
520 
521                 OPEN next_action_id;
522                 FETCH next_action_id into v_next_action_id;
523                 CLOSE next_action_id;
524                 hr_nonrun_asact.insact(v_next_action_id,
525                                 csr_rec.assignment_id,
526                                 p_payroll_action_id,
527                                 p_chunk,
528                                null);
529                 hr_nonrun_asact.insint(v_next_action_id,csr_rec.assignment_action_id);
530                 hr_nonrun_asact.insint(v_next_action_id,csr_rec.datafile_action_id);
531 
532                 IF g_debug
533                 THEN
534                         hr_utility.set_location('Assignment_ID                  '||csr_rec.assignment_id,35);
535                         hr_utility.set_location('New Ass Action ID              '||v_next_action_id,40);
536                         hr_utility.set_location('Locked Archive Action ID       '||csr_rec.assignment_action_id,45);
540     END IF;
537                         hr_utility.set_location('Locked Data file Action ID     '||csr_rec.datafile_action_id,50);
538                 END IF;
539         END LOOP;
541 END IF;
542 
543  exception
544     when others then
545     hr_utility.set_location('error raised in assignment_action_code procedure ',5);
546     raise;
547  end assignment_action_code;
548 
549 
550  --------------------------------------------------------------------------
551   -- This Procedure Actually Calls the Payment Summary Report.
552  --------------------------------------------------------------------------
553 
554 procedure spawn_archive_reports
555   is
556  l_count                number :=0;
557  ps_request_id          NUMBER;
558  l_formula_id           ff_formulas_f.formula_id%TYPE;
559  l_payroll_action_id    pay_payroll_actions.payroll_action_id%TYPE;
560  l_sort_order1      varchar2(40);
561  l_sort_order2      varchar2(40):=null;
562  l_sort_order3      varchar2(40):=null;
563  l_sort_order4      varchar2(40):=null;
564  l_passed_sort_order    varchar2(40);
565  l_print_style          VARCHAR2(2);
566  l_current_chunk_number pay_payroll_actions.current_chunk_number%TYPE;
567  l_print_together       VARCHAR2(80);
568  l_print_return         BOOLEAN;
569  l_duplex_print_flag    varchar2(2);
570  l_template_name  varchar2(80);      -- Bug 4859876
571  l_program_name  varchar2(80);       -- Bug 4891196
572 
573 
574 
575  cursor csr_get_current_chunk_number(p_payroll_action_id number) is
576  select p.current_chunk_number
577  from pay_payroll_actions p
578  where payroll_action_id = p_payroll_action_id;
579 
580 
581  cursor csr_get_formula_id(p_formula_name VARCHAR2) IS
582  SELECT a.formula_id
583  FROM     ff_formulas_f a,
584           ff_formula_types t
585  WHERE a.formula_name      = p_formula_name
586           AND business_group_id   IS NULL
587           AND legislation_code    = 'AU'
588           AND a.formula_type_id   = t.formula_type_id
589           AND t.formula_type_name = 'Oracle Payroll';
590 
591 
592  cursor csr_get_print_options(p_payroll_action_id NUMBER) IS
593  SELECT printer,
594           print_style,
595           decode(save_output_flag, 'Y', 'TRUE', 'N', 'FALSE') save_output,
596           number_of_copies  /* Bug: 3768288 */
597     FROM  pay_payroll_actions pact,
598           fnd_concurrent_requests fcr
599     WHERE fcr.request_id = pact.request_id
600     AND   pact.payroll_action_id = p_payroll_action_id;
601 
602   /*Bug# 5743270
603     Cursor checks whether any assignment exist for which Printed Payment Summary(PUI) need to be produced
604     */
605   cursor csr_is_assignemnt_exist (p_payroll_action_id pay_payroll_actions.payroll_action_id%TYPE) is
606   select count(ppav.assignment_id)
607     from   pay_au_eoy_values_v ppav,
608            pay_payroll_actions ppa,
609            pay_assignment_actions pac
610            where ppa.payroll_action_id= p_payroll_action_id
611            and   ppav.payroll_action_id =pay_core_utils.get_parameter('ARCHIVE_ID',ppa.legislative_parameters)
612            and   ppa.report_type='AU_PAYMENT_SUMMARY_REPORT'
613            and   ppav.assignment_id=pac.assignment_id
614            and   ppav.X_REPORTING_FLAG = 'YES'
615            and   ppav.X_CURR_TERM_0_BAL_FLAG='NO'
616            and   pac.payroll_action_id=p_payroll_action_id
617            and decode(pay_core_utils.get_parameter('SS_PREF',ppa.legislative_parameters),'N',ss_pref(pac.assignment_id),'N') ='N'
618            ;
619 
620 
621  rec_print_options  csr_get_print_options%ROWTYPE;
622   l_assignment_exist number;  /* Bug#5743270 */
623  Function get_sort_order_value(l_passed_sort_order in varchar2)
624  return varchar2 is
625  l_sort_order varchar2(40);
626  begin
627    if    l_passed_sort_order  = 'EMPLOYEE_TYPE'
628    then  l_sort_order := 'employee_type';
629    elsif l_passed_sort_order  = 'ASSIGNMENT_LOCATION'
630    then  l_sort_order := 'assignment_location';
631    elsif l_passed_sort_order  = 'EMPLOYEE_NUMBER'
632    then  l_sort_order := 'employee_number';
633    elsif l_passed_sort_order  = 'PAYROLL'
634    then  l_sort_order := 'payroll';
635    elsif l_passed_sort_order  = 'EMPLOYEE_SURNAME'
636    then  l_sort_order := 'employee_last_name';
637    else
638          l_sort_order:=null;
639    end if;
640    return l_sort_order;
641  end get_sort_order_value;
642 
643 
644 Begin
645   ps_request_id := -1;
646 
647   Begin
648      LOOP
649        l_count := l_count + 1;
650        hr_utility.set_location('Before payroll action' , 25);
651        hr_utility.set_location('mag_internal ' || pay_mag_tape.internal_prm_names(l_count) , 105);
652        hr_utility.set_location('mag_internal ' || pay_mag_tape.internal_prm_values(l_count) , 115);
653        l_passed_sort_order:=pay_mag_tape.internal_prm_names(l_count);
654        IF    pay_mag_tape.internal_prm_names(l_count)  = 'TRANSFER_PAYROLL_ACTION_ID'
655        THEN
656              l_payroll_action_id := to_number(pay_mag_tape.internal_prm_values(l_count));
657              hr_utility.set_location('payroll_action ',0);
658        ELSIF l_passed_sort_order= 'SORT_ORDER1'
659        THEN
660              l_sort_order1 := pay_mag_tape.internal_prm_values(l_count);
661                           hr_utility.set_location('in sort order1 ',1);
662        ELSIF l_passed_sort_order= 'SORT_ORDER2'
663        THEN
664              l_sort_order2 := pay_mag_tape.internal_prm_values(l_count);
665              hr_utility.set_location('in sort_order 2 ',2);
666        ELSIF l_passed_sort_order= 'SORT_ORDER3'
667        THEN
668              hr_utility.set_location('in sort_order3 ',3);
672           l_sort_order4 := pay_mag_tape.internal_prm_values(l_count);
669              l_sort_order3 := pay_mag_tape.internal_prm_values(l_count);
670        ELSIF l_passed_sort_order= 'SORT_ORDER4'
671        THEN
673              hr_utility.set_location('in sort_orderr4 ',4);
674     /* Bug 3132172 Duplex Printing Support*/
675        ELSIF pay_mag_tape.internal_prm_names(l_count)  = 'DUPLEX_PRINT_FLAG'
676        THEN
677          l_duplex_print_flag := pay_mag_tape.internal_prm_values(l_count);
678              hr_utility.set_location('in duplex_print_flag',5);
679      /* Bug 4859876 - Template Code for PDF Output */
680        ELSIF pay_mag_tape.internal_prm_names(l_count) = 'TMPL'
681        THEN
682          l_template_name := pay_mag_tape.internal_prm_values(l_count);
683             hr_utility.set_location('in Template Names'||l_template_name,6);
684        END IF;
685 
686      END LOOP;
687      EXCEPTION
688        WHEN no_data_found THEN
689             -- Use this exception to exit loop as no. of plsql tab items
690             -- is not known beforehand. All values should be assigned.
691        NULL;
692        WHEN value_error THEN
693        NULL;
694    End;
695 
696 
697  l_sort_order1:=get_sort_order_value(l_sort_order1);
698  hr_utility.set_location('getting sort_order1'||l_sort_order1, 121);
699  l_sort_order2:=get_sort_order_value(l_sort_order2);
700  hr_utility.set_location('getting sort_order2'||l_sort_order2, 122);
701  l_sort_order3:=get_sort_order_value(l_sort_order3);
702  hr_utility.set_location('getting sort_order3'||l_sort_order3, 123);
703  l_sort_order4:=get_sort_order_value(l_sort_order4);
704  hr_utility.set_location('getting sort_order4'||l_sort_order4, 124);
705 
706 
707 
708 hr_utility.set_location('getting current chunk_number ', 125);
709 
710  OPEN csr_get_current_chunk_number(l_payroll_action_id);
711  fetch csr_get_current_chunk_number into l_current_chunk_number;
712  CLOSE csr_get_current_chunk_number;
713 
714  /* Bug#5743270
715     Cursor checks whether any assignment exist for which Printed Payment Summary(PUI) need to be produced
716  */
717  OPEN csr_is_assignemnt_exist(l_payroll_action_id);
718  fetch csr_is_assignemnt_exist into l_assignment_exist;
719  CLOSE csr_is_assignemnt_exist;
720 
721 
722  if l_current_chunk_number <> 0  and  l_assignment_exist > 0
723  then
724 
725       hr_utility.set_location('Afer payroll action ' || l_payroll_action_id , 125);
726       --hr_utility.set_location('sort ' || l_sort_order,166);
727       hr_utility.set_location('Before calling report',24);
728 
729        OPEN csr_get_print_options(l_payroll_action_id);
730        FETCH csr_get_print_options INTO rec_print_options;
731        CLOSE csr_get_print_options;
732        --
733        l_print_together := nvl(fnd_profile.value('CONC_PRINT_TOGETHER'), 'N');
734        --
735        -- Set printer options
736        l_print_return := fnd_request.set_print_options
737                            (printer        => rec_print_options.printer,
738                             style          => rec_print_options.print_style,
739                             copies         => rec_print_options.number_of_copies, /* Bug: 3768288 */
740                             save_output    => hr_general.char_to_bool(rec_print_options.save_output),
741                             print_together => l_print_together);
742     -- Submit report
743       hr_utility.set_location('payroll_action id    '|| l_payroll_action_id,25);
744 
745       /* Bug 4891196 - Determine Report to be submitted,
746          i.  If Template is Null, then Postscript output
747          ii. If Template is NOT Null, then XML/PDF output.
748       */
749 
750       if  l_template_name is NULL
751       then
752             l_program_name := 'PYAUPSRP_PS';
753       else
754             l_program_name := 'PYAUPSRP';
755       end if;
756 
757 ps_request_id := fnd_request.submit_request
758  ('PAY',
759   l_program_name,                               -- Bug 4891196
760    null,
761    null,
762    false,
763    'P_PAYROLL_ACTION_ID='||to_char(l_payroll_action_id),
764    'P_SORT_ORDER1='||l_sort_order1,
765    'P_SORT_ORDER2='||l_sort_order2,
766    'P_SORT_ORDER3='||l_sort_order3,
767    'P_SORT_ORDER4='||l_sort_order4,
768    'P_DUPLEX_PRINT_FLAG='|| l_duplex_print_flag, -- Bug 3132172
769    'P_TEMPLATE_NAME='||l_template_name,          -- Bug 4859876
770    'BLANKPAGES=NO',
771    NULL,   NULL,   NULL,
772    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
773    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
774    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
775    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
776    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
777    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
778    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
779    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
780    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
781    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
782    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
783    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
784    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
785    NULL,   NULL,   NULL,   NULL,   NULL,   NULL,
786    NULL,   NULL,   NULL,   NULL,   NULL
787 );
788 
789       hr_utility.set_location('After calling report',24);
790 
791 
792 end if;
793 
794         hr_utility.set_location('Before calling formula',22);
795 
796        OPEN csr_get_formula_id('AU_PS_REPORT');
797        FETCH csr_get_formula_id INTO l_formula_id;
798        CLOSE csr_get_formula_id;
799 
800     pay_mag_tape.internal_prm_names(1) := 'NO_OF_PARAMETERS';
801     pay_mag_tape.internal_prm_values(1) := '5';
802     pay_mag_tape.internal_prm_names(2) := 'NEW_FORMULA_ID';
803     pay_mag_tape.internal_prm_values(2) := to_char(l_formula_id);
804     pay_mag_tape.internal_prm_names(3) := 'PS_REQUEST_ID';
805     pay_mag_tape.internal_prm_values(3) := to_char(ps_request_id);
806     pay_mag_tape.internal_prm_names(4) := 'PAYROLL_ACTION_ID';
807     pay_mag_tape.internal_prm_values(4) := to_char(l_payroll_action_id);
808     pay_mag_tape.internal_prm_names(5) := 'SORT_ORDER1';
809     pay_mag_tape.internal_prm_values(5) :=l_sort_order1;
810     pay_mag_tape.internal_prm_names(6) := 'SORT_ORDER2';
811     pay_mag_tape.internal_prm_values(6) :=l_sort_order2;
812     pay_mag_tape.internal_prm_names(7) := 'SORT_ORDER3';
813     pay_mag_tape.internal_prm_values(7) :=l_sort_order3;
814     pay_mag_tape.internal_prm_names(8) := 'SORT_ORDER4';
815     pay_mag_tape.internal_prm_values(8) :=l_sort_order4;
816 --  hr_utility.trace_off;
817 end spawn_archive_reports;
818 
819 ---
820 -- Bug 4726357 Added to check whether Self Service Option is enabled for the employee
821 ---
822 
823 function ss_pref(p_assignemnt_id per_assignments_f.assignment_id%type) return varchar2
824 is
825 
826 l_bg_id number;
827 l_loc_id number;
828 l_org_id number;
829 l_person_id number;
830 l_online_opt char(1);
831 
832 /* Cursor to get the business group id, location id, organization id and person id */
833 cursor asg_info is
834 select  paf.business_group_id, paf.location_id, paf.organization_id,paf.person_id
835 from per_assignments_f paf
836 where paf.assignment_id = p_assignemnt_id
837   and   paf.effective_start_date =
838     (select max(effective_start_date)
839      from per_assignments_f paf2
840      where paf2.assignment_id = paf.assignment_id
841      );
842 
843 /* Cursor to get the option sets at different level i.e Person level, Location Level, Organization Level and
844 Business group level. The cursor fetches option in hierarchy . The person level will override location.
845 Location overrides HR Organization, and HR Organization overrides the option defined at Business Group */
846 
847 cursor ss_pref (c_bg_id number,c_loc_id number,c_org_id number, c_person_id number)
848 is
849 SELECT online_opt
850 FROM
851 (
852        Select PEI_INFORMATION2 online_opt, 1 sort_col
853         from PER_PEOPLE_EXTRA_INFO ppit
854         where   ppit.person_id=c_person_id
855           and  ppit.pei_information1= 'PAYMENTSUMMARY'
856       and  ppit.information_type='HR_SELF_SERVICE_PER_PREFERENCE'
857         union
858         Select LEI_INFORMATION2 online_opt, 2 sort_col
859         FROM hr_location_extra_info hlei
860         WHERE hlei.location_id = c_loc_id
861       And hlei.lei_information1= 'PAYMENTSUMMARY'
862           AND hlei.information_type = 'HR_SELF_SERVICE_LOC_PREFERENCE'
863         UNION
864         SELECT org_information2 online_opt,
865                3 sort_col
866         FROM hr_organization_information hoi
867         WHERE hoi.organization_id = c_org_id
868       and hoi.org_information1 = 'PAYMENTSUMMARY'
869           AND hoi.org_information_context = 'HR_SELF_SERVICE_ORG_PREFERENCE'
870          UNION
871          SELECT org_information2 online_opt,
872                 4 sort_col
873          FROM hr_organization_information hoi
874          WHERE hoi.organization_id = c_bg_id
875            And hoi.org_information1 = 'PAYMENTSUMMARY'
876                AND hoi.org_information_context = 'HR_SELF_SERVICE_BG_PREFERENCE'
877     )
878     WHERE online_opt IS NOT NULL
879     ORDER BY sort_col;
880 Begin
881  open asg_info;
882  fetch asg_info into l_bg_id,l_loc_id,l_org_id,l_person_id;
883  close asg_info;
884 
885 
886  open ss_pref (l_bg_id,l_loc_id,l_org_id,l_person_id);
887  fetch ss_pref into l_online_opt;
888 
889 /*If no option set at any level online option will be set as No */
890  if ss_pref%NOTFOUND THEN
891   l_online_opt := 'N';
892  end if;
893   close ss_pref;
894 
895 return l_online_opt;
896 end;
897 
898 END pay_au_payment_summary_report;