DBA Data[Home] [Help]

PACKAGE BODY: APPS.PAY_EVENTS_WRAPPER

Source


1 PACKAGE BODY pay_events_wrapper AS
2 /* $Header: pyevtwrp.pkb 120.1 2006/02/13 02:52:31 alogue noship $ */
3 /*
4     +======================================================================+
5     |               Copyright (c) 2002 Oracle Corporation UK               |
6     |                    Thames Valley Park, Reading, UK                   |
7     |                        All rights reserved.                          |
8     +======================================================================+
9     File Name   : pyevtwrp.pkh
10 
11     Description : A wrapper on top of the Payroll Events Model interpreter
12                   for use with the summarisation collection programs which
13                   are used to increase the performance of the Daily Business
14                   Intelligence portlet queries.
15 
16     Change History
17     --------------
18     Name           Date        Version Bug     Text
19     -------------- ----------- ------- ------- ------------------------------------
20     Ed Jones       31-May-2002 115.0           Initial (Stub) version
21     Ed Jones       31-May-2002 115.1           Added dbdrv lines
22                                                Removed dbms_output
23     Ed Jones       31-May-2002 115.2           Corrected invalid dbdrv lines
24     Ed Jones       14-Jun-2002 115.3           Replaced stubs with proper
25                                                code, moved wrapper specific
26                                                detailed output fields from
27                                                interpreter to an additional
28                                                cache table here (dated table
29                                                extras global variable)
30     Ed Jones       02-Jul-2002 115.4           Added refresh period start
31                                                and end dates to the
32                                                get_refresh_periods routine
33                                                and pass these to the interpreter
34                                                rather than the effective assignment
35                                                dates
36     Ed Jones       02-Jul-2002 115.5           Removed owner from join to
37                                                all_tab_columns
38     Ed Jones       23-Jul-2002 115.6           Add debugging mode and allow
39                                                messages to be sent to conc.
40                                                manager output file
41     Ed Jones       23-Jul-2002 115.7           Added more debug information
42                                                Send conc. messages to log
43     Ed Jones       23-Jul-2002 115.8           Add supervisor ID column changes
44                                                separately to normal payroll event
45                                                model updates, this is to detect
46                                                and record old and new supervisors
47                                                in the list of refresh records
48     Ed Jones       27-Mar-2003 115.9   2870801 Changes to support date track
49                                                updates to supervisor as well as
50                                                corrections.
51     Ed Jones       10-Apr-2003 115.10          Changes to pick up correct start date
52                                                for updated supervisor correctly
53     Ed Jones       02-Jun-2003 115.11  2984406 Moved pay_interpreter_pkg.event_group_tables
54                                                call and reset of g_DATED_TABLE_EXTRAS
55 					       cache to a separate procedure (from
56 					       get_event_details) so that it's only
57 					       called once per run.
58 					       Don't pass around event group name
59 					       parameter, use the global ID populated in
60 					       the one-off init_event_group_cache
61 					       procedure.
62 					       Major changes to the way in which affected
63 					       assignments are detected, see specific
64 					       sections for details (search for this bug).
65     Ed Jones       07-Jul-2003 115.13          Moved various cursors to be visible at package
66                                                level for ease of access by diagnostics
67 					       routines.
68 					       Made dt update SQL building function accessible
69 					       for this reason too.
70 					       Change csr_inserts_deletes cursor to decode
71 					       various event types to match update types.
72 					       Corrections cursor looks for C type updates
73 					       as well as U (database updates may be stored
74 					       in the incident register as corrections)
75 				       3033981 Changed incident register accessing cursors
76 				               to get surrogate key and pass that on to
77 					       the event interpreter, if the table in use
78 					       is element entries.
79     Ed Jones       07-Jul-2003 115.14          Remove 'show errors' for gscc
80     Andy Logue     23-DEC-2003 115.15  3329824 Performance fix
81     Andy Logue     05-JAN-2004 115.16          Performance fix
82     N Bristow      26-JAN-2004 115.17          get_assignments_affected changed to drive
83                                                off pay_process_events and to only use
84                                                salary entries.
85     N Bristow      10-MAR-2004 115.18          Performance changes, the PL/SQL
86                                                tables were being over
87                                                referenced. Change these tables
88                                                to use a hash cache.
89     Andy Logue     13-FEB-2006 115.19          Schema clone for all_tab_columns.
90     ===============================================================================
91 */
92     --
93     -- < PRIVATE TYPES > -----------------------------------------------------
94     TYPE t_dated_table_extras_rec IS RECORD(
95         has_supervisor_id         VARCHAR2(1),
96         has_location_id           VARCHAR2(1),
97         has_assignment_id         VARCHAR2(1),
98         sql_statement             VARCHAR2(32767)
99     );
100     TYPE t_dated_table_extras_tab IS
101         TABLE OF t_dated_table_extras_rec
102         INDEX BY BINARY_INTEGER;
103 --
104     type t_indexing_rec is record(
105          start_ptr number
106     );
107 --
108     type t_indexing_tab is table of t_indexing_rec index by BINARY_INTEGER;
109 --
110     type t_location_chn_rec is record
111     (
112         supervisor_id number,
113         location_id   number,
114         summary_ptr   number,
115         next_ptr      number
116     );
117 --
118     type t_location_chn_tab is table of t_location_chn_rec
119      index by BINARY_INTEGER;
120 --
121     g_supervisor_hash_tab t_indexing_tab;
122     g_location_chn_tab    t_location_chn_tab;
123 
124 --
125     --
126     -- < PRIVATE CONSTANTS > -------------------------------------------------
127     --
128     -- The event model processing mode and other animals
129     c_PROCESS_MODE          CONSTANT VARCHAR2(30)   := 'ASG_CREATION';
130     c_ASSIGNMENTS_TABLE     CONSTANT VARCHAR2(30)   := 'per_all_assignments_f';
131     c_OUTPUT_BUFFER         CONSTANT NUMBER         := 2000000;
132     c_OUTPUT_LINE_LENGTH    CONSTANT NUMBER         := 255;
133     --
134     -- < PRIVATE GLOBALS > ---------------------------------------------------
135     --
136     g_debugging             BOOLEAN := FALSE;
137     g_concurrent            BOOLEAN := FALSE;
138     --
139     -- How long did the last run take
140     g_SECONDS_ELAPSED       NUMBER  := 0;
141     --
142     -- Cached information about an event group
143     g_DATED_TABLE_EXTRAS    t_dated_table_extras_tab;
144     g_EVENT_GROUP_ID        NUMBER := NULL;
145     --
146     -- Globals for record looping
147     g_FIRST_RECORD 	    NUMBER := 0;
148     g_LAST_RECORD 	    NUMBER := 0;
149     g_CURRENT_RECORD 	    NUMBER := 0;
150     --
151     -- < CURSORS > -----------------------------------------------------------
152     --
153 --
154     CURSOR csr_all_changes(p_st IN DATE,p_en IN DATE) IS
155         SELECT
156                     ppe.assignment_id,
157                     ppe.surrogate_key,
158                     peu.dated_table_id,
159                     MIN(ppe.effective_date)   effective_start_date,
160                     MAX(ppe.effective_date)   effective_end_date
161         FROM        pay_process_events      ppe,
162                     pay_event_updates       peu
163         WHERE       ppe.creation_date BETWEEN p_st AND p_en
164         AND         ppe.event_update_id = peu.event_update_id
165         GROUP BY    ppe.assignment_id,ppe.surrogate_key, peu.dated_table_id
166         ORDER BY    ppe.assignment_id, ppe.surrogate_key;
167 --
168     -- Get the inserts into and deletes from the tables we care about
169     CURSOR csr_inserts_deletes(p_evt IN NUMBER,p_st IN DATE,p_en IN DATE) RETURN csr_return IS
170         SELECT
171 	            ppe.assignment_id,
172 	            peu.dated_table_id,
173 	            ppe.surrogate_key,
174                     MIN(ppe.effective_date)   start_date,
175                     MAX(ppe.effective_date)   end_date
176         FROM        pay_process_events      ppe,
177                     pay_event_updates       peu
178         WHERE       ppe.creation_date BETWEEN p_st AND p_en
179         AND         ppe.event_update_id = peu.event_update_id
180         AND         substr(peu.event_type,1,1) in ('D','I','Z')
181         AND EXISTS (
182                     SELECT  'X'
183                     FROM    pay_datetracked_events pde
184                     WHERE   pde.event_group_id = p_evt
185                     AND     pde.dated_table_id = peu.dated_table_id
186                     AND     pde.update_type = SUBSTR(DECODE(peu.event_type,'ZAP','D',peu.event_type),1,1)
187         )
188         GROUP BY    ppe.assignment_id,peu.dated_table_id,ppe.surrogate_key;
189     --
190     -- Get the updates (date-track corrections) to columns we care about, excluding supervisor ID
191     CURSOR csr_dt_corrections(p_evt IN NUMBER,p_st IN DATE,p_en IN DATE) RETURN csr_return IS
192         SELECT
193 	            ppe.assignment_id,
194 	            peu.dated_table_id,
195                     ppe.surrogate_key,
196                     MIN(ppe.effective_date)   start_date,
197                     MAX(ppe.effective_date)   end_date
198         FROM        pay_process_events      ppe,
199                     pay_event_updates       peu
200         WHERE       ppe.creation_date BETWEEN p_st AND p_en
201         AND         ppe.event_update_id = peu.event_update_id
202         AND         substr(peu.event_type,1,1) IN ('U','C')
203         AND EXISTS (
204                     SELECT  'X'
205                     FROM    pay_datetracked_events  pde,
206                             pay_dated_tables        pdt
207       	            WHERE   pde.event_group_id = p_evt
208       	            AND     pde.dated_table_id = peu.dated_table_id
209                     AND     pdt.dated_table_id = pde.dated_table_id
210 	            AND     pde.column_name = peu.column_name
211                     AND     NOT (pdt.table_name = 'PER_ALL_ASSIGNMENTS_F' AND pde.column_name = 'SUPERVISOR_ID')
212 	            AND     pde.update_type = 'C'
213                    )
214         GROUP BY    ppe.assignment_id,peu.dated_table_id,ppe.surrogate_key;
215         --
216         -- Decode the description column of pay_process_events to obtain the
217         -- before and after values, just for the supervisor ID column on
218         -- per_all_assignments_f, and only if that column is one of the ones
219         -- we're tracking via our event group. Group by supervisor ID and
220         -- optionally location ID and return the earliest and latest effective
221         -- dates that were affected by the change
222 	-- 2984406: Changes for performance
223         CURSOR csr_supv_corrections(
224             cp_evt      IN NUMBER,
225             cp_st       IN DATE,
226             cp_en       IN DATE,
227             cp_str      IN VARCHAR2
228         ) RETURN csr_return IS
229             SELECT  TO_NUMBER(DECODE(sic.column_name,'SUPERVISOR_ID',sic.id,NULL))  supervisor_id,
230                     DECODE(cp_str,'Y',paaf.location_id,c_BLANK_LOCATION_ID)         location_id,
231 		    NULL                                                            dummy,
232                     MIN(sic.effective_date)                                         effective_start_date,
233                     MAX(sic.effective_date)                                         effective_end_date
234             FROM    (
235                         -- Get the 'before' information, i.e. the ID before the '->' character sequence
236                         SELECT  /*+ ordered index(ppe pay_process_events_n3) */
237 	                        DECODE(SUBSTR(ppe.description,1,INSTR(ppe.description,' -> ')-1),'<null>',NULL,SUBSTR(ppe.description,1,INSTR(ppe.description,' -> ')-1)) id,
238                                 ppe.effective_date,
239                                 ppe.assignment_id,
240                                 peu.dated_table_id,
241                                 peu.column_name
242                         FROM    pay_process_events  ppe,
243                                 pay_event_updates   peu,
244                                 pay_dated_tables    pdt,
245 				pay_datetracked_events pde
246                         WHERE   INSTR(ppe.description,' -> ') > 0
247                         AND     SUBSTR(ppe.description,1,6) <> '<null>'
248                         AND     peu.event_update_id = ppe.event_update_id
249                         AND     peu.dated_table_id = pdt.dated_table_id
250                         AND     pdt.table_name = 'PER_ALL_ASSIGNMENTS_F'
251                         AND     peu.column_name = 'SUPERVISOR_ID'
252 			AND     pde.update_type = 'C'
253 			AND     pde.column_name = peu.column_name
254 			AND     ppe.creation_date BETWEEN cp_st AND cp_en
255 			AND     cp_evt = pde.event_group_id
256 			AND     pde.dated_table_id = peu.dated_table_id
257                         UNION
258                         -- Add the 'after' information, i.e. the ID after the '->' character sequence, don't UNION ALL 'cos that would give us duplicates
259                         SELECT  /*+ ordered index(ppe pay_process_events_n3) */
260 	                        DECODE(SUBSTR(ppe.description,INSTR(ppe.description,' -> ')+4),'<null>',NULL,SUBSTR(ppe.description,INSTR(ppe.description,' -> ')+4)) id,
261                                 ppe.effective_date,
262                                 ppe.assignment_id,
263                                 peu.dated_table_id,
264                                 peu.column_name
265                         FROM    pay_process_events  ppe,
266                                 pay_event_updates   peu,
267                                 pay_dated_tables    pdt,
268 				pay_datetracked_events pde
269                         WHERE   INSTR(ppe.description,' -> ') > 0
270                         AND     SUBSTR(ppe.description,length(ppe.description)-5) <> '<null>'
271                         AND     peu.event_update_id = ppe.event_update_id
275 			AND     pde.update_type = 'C'
272                         AND     peu.dated_table_id = pdt.dated_table_id
273                         AND     pdt.table_name = 'PER_ALL_ASSIGNMENTS_F'
274                         AND     peu.column_name = 'SUPERVISOR_ID'
276 			AND     pde.column_name = peu.column_name
277 			AND     ppe.creation_date BETWEEN cp_st AND cp_en
278 	                AND     cp_evt = pde.event_group_id
279 			AND     pde.dated_table_id = pdt.dated_table_id
280                     )                       sic,
281                     per_all_assignments_f   paaf
282             -- Join to the assignment at the effective date of the change to get the location
283             WHERE   sic.effective_date BETWEEN paaf.effective_start_date AND paaf.effective_end_date
284             AND     paaf.assignment_id      = sic.assignment_id
285             GROUP BY
286                     TO_NUMBER(DECODE(sic.column_name,'SUPERVISOR_ID',sic.id,NULL)),
287                     DECODE(cp_str,'Y',paaf.location_id,c_BLANK_LOCATION_ID);
288 		            --
289 	-- Get a list of the tables that are in our event group
290         CURSOR csr_table_list(p_evt IN NUMBER) RETURN csr_return IS
291             SELECT DISTINCT pdt.dated_table_id,NULL,pdt.table_name,NULL,NULL
292             FROM   pay_dated_tables pdt,
293                    pay_datetracked_events pde
294             WHERE  pde.dated_table_id = pdt.dated_table_id
295             AND    pde.event_group_id = p_evt
296             AND    pde.update_type = 'U';
297 --
298 procedure get_summary_idx(p_super_id        in            number,
299                           p_location_id     in            number,
300                           p_idx                out nocopy number,
301                           p_summary_refresh in out nocopy t_summary_refresh_tab_type
302                          )
303 is
304 hash_key number;
305 loc_idx  number;
306 sum_idx  number;
307 prev_idx number;
308 l_found  boolean;
309 begin
310 --
311    hash_key := (p_super_id mod 1009 ) + 1;
312 --
313    begin
314 --
315        if (g_supervisor_hash_tab.exists(hash_key)) then
316 --
317           loc_idx := g_supervisor_hash_tab(hash_key).start_ptr;
318 --
319           l_found := FALSE;
320           while (l_found <> TRUE and loc_idx is not null) loop
321              if (   g_location_chn_tab(loc_idx).supervisor_id = p_super_id
322                 and g_location_chn_tab(loc_idx).location_id = p_location_id)
323              then
324                  l_found := TRUE;
325              else
326                  prev_idx := loc_idx;
327                  loc_idx := g_location_chn_tab(loc_idx).next_ptr;
328              end if;
329           end loop;
330 --
331           /* OK if we didn't find one the create one */
332           if (l_found = FALSE) then
333             loc_idx := g_location_chn_tab.count + 1;
334             g_location_chn_tab(loc_idx).supervisor_id := p_super_id;
335             g_location_chn_tab(loc_idx).location_id   := p_location_id;
336             g_location_chn_tab(loc_idx).summary_ptr   := null;
337             g_location_chn_tab(loc_idx).next_ptr      := null;
338 --
339             -- Set the previous pointer.
340             g_location_chn_tab(prev_idx).next_ptr     := loc_idx;
341           end if;
342 --
343        else
344 --
345           loc_idx := g_location_chn_tab.count + 1;
346           g_location_chn_tab(loc_idx).supervisor_id := p_super_id;
347           g_location_chn_tab(loc_idx).location_id   := p_location_id;
348           g_location_chn_tab(loc_idx).summary_ptr   := null;
349           g_location_chn_tab(loc_idx).next_ptr      := null;
350 --
351           g_supervisor_hash_tab(hash_key).start_ptr := loc_idx;
352        end if;
353 --
354    end;
355 --
356    /* OK we should now have a row for the location table.
357       Need to see if we have a row in the summary table
358    */
359 --
360    if (g_location_chn_tab(loc_idx).summary_ptr is null) then
361 --
362      sum_idx := p_summary_refresh.count + 1;
363 --
364      p_summary_refresh(sum_idx).supervisor_id := p_super_id;
365      p_summary_refresh(sum_idx).location_id   := p_location_id;
366 --
367      g_location_chn_tab(loc_idx).summary_ptr := sum_idx;
368 --
369    end if;
370 --
371    p_idx := g_location_chn_tab(loc_idx).summary_ptr;
372 --
373 end get_summary_idx;
374     --
375     -- < PRIVATE FUNCTIONS > -------------------------------------------------
376     --
377     -- Increment a data
378     FUNCTION inc_date(p_date IN DATE) RETURN DATE IS
379     BEGIN
380         IF p_date < hr_general.end_of_time THEN
381             RETURN p_date + 1;
382         ELSE
383             RETURN p_date;
384         END IF;
385     END inc_date;
386     --
387     -- Decrement a date
388     FUNCTION dec_date(p_date IN DATE) RETURN DATE IS
389     BEGIN
390         IF p_date > hr_general.start_of_time THEN
391             RETURN p_date - 1;
392         ELSE
393             RETURN p_date;
394         END IF;
395     END dec_date;
396     --
397     -- Get the business group of an assignment
398     FUNCTION get_business_group_id(p_assignment_id IN NUMBER) RETURN NUMBER IS
399         --
400         CURSOR csr_bg(cp_ass_id IN NUMBER) IS
401             SELECT  business_group_id
402             FROM    per_assignments_f
403             WHERE   assignment_id = cp_ass_id;
404         --
405         l_business_group_id     NUMBER;
406         --
407     BEGIN
408         OPEN csr_bg(p_assignment_id);
412         RETURN l_business_group_id;
409         FETCH csr_bg INTO l_business_group_id;
410         CLOSE csr_bg;
411         --
413     END get_business_group_id;
414     --
415     -- Find the information we need from the dated table cache
416     FUNCTION query_dated_table_cache(p_dated_table_id IN NUMBER) RETURN NUMBER IS
417         --
418         l_tab_idx NUMBER;
419         --
420     BEGIN
421         --
422         -- Try to find the table the event occurred on in the cache
423         l_tab_idx := -1;
424         --
425         IF NVL(pay_interpreter_pkg.t_distinct_tab.FIRST,0) > 0 THEN
426             FOR k IN pay_interpreter_pkg.t_distinct_tab.FIRST .. pay_interpreter_pkg.t_distinct_tab.LAST LOOP
427                 IF pay_interpreter_pkg.t_distinct_tab(k).table_id = p_dated_table_id THEN
428                     msg('Found dated table '||p_dated_table_id||' at index '||k);
429                     l_tab_idx := k;
430                     EXIT;
431                 END IF;
432             END LOOP;
433         ELSE
434             -- Log some debugging info and bail
435             msg('No dated table information was cached.');
436             RAISE dated_table_cache_empty;
437         END IF;
438         --
439         -- Bail if we didn't find the cached info we wanted
440         IF l_tab_idx = -1 THEN
441             msg('Dated table '||p_dated_table_id||' was not cached.');
442             RAISE dated_table_cache_miss;
443         END IF;
444         --
445         RETURN l_tab_idx;
446     END query_dated_table_cache;
447     --
448     -- Return the value of the elapsed time global populated when a full run is
449     -- completed
450     FUNCTION get_elapsed_time RETURN NUMBER IS
451     BEGIN
452         RETURN g_SECONDS_ELAPSED;
453     END get_elapsed_time;
454     --
455     -- Get the time taken to execute the last run
456     FUNCTION get_elapsed_time_text RETURN VARCHAR2 IS
457     BEGIN
458         RETURN 'Elapsed time: '||TO_CHAR(get_elapsed_time,'fm99999990.000')||' seconds';
459     END get_elapsed_time_text;
460     --
461     -- < PRIVATE PROCEDURES > ------------------------------------------------
462     --
463     -- Get the event details for a single assignment ID
464     PROCEDURE get_event_details(
465         p_start_date        IN      DATE,
466         p_end_date          IN      DATE,
467         p_assignment_id     IN      NUMBER,
468 	p_element_entry_id  IN      NUMBER,
469         p_detailed_output   IN OUT  NOCOPY pay_interpreter_pkg.t_detailed_output_table_type,
470         p_proration_dates   IN OUT  NOCOPY pay_interpreter_pkg.t_proration_dates_table_type
471     ) IS
472         -- Business group ID
473         l_business_group_id     NUMBER;
474         --
475         -- Temporary table variables to hold the results from the event model
476         -- procedure calls. These results aren't used
477         l_dynamic_sql           pay_interpreter_pkg.t_dynamic_sql_tab;
478         l_proration_change_type pay_interpreter_pkg.t_proration_type_table_type;
479         l_proration_type        pay_interpreter_pkg.t_proration_type_table_type;
480         --
481     BEGIN
482         msg('Getting event details for assignment: '||p_assignment_id);
483         --
484         -- Get the business group ID
485         l_business_group_id := get_business_group_id(p_assignment_id);
486         --
487         -- Get and parse the events that occurred. Note that we don't call
488         -- unique_sort as we do in entry_affected, since we do actually want
489         -- a list of all the events that occurred and the effective date of
490         -- each one, not just the unique dates, since we'll later merge the
491         -- events up to the supervisor level
492         pay_interpreter_pkg.event_group_tables_affected(
493             p_element_entry_id,
494 	    NULL,
495 	    g_EVENT_GROUP_ID,
496     	    p_assignment_id,
497 	    l_business_group_id,
498 	    p_start_date,
499     	    p_end_date,
500 	    NULL,
501 	    NULL,
502             c_PROCESS_MODE,
503 	    l_dynamic_sql,
504 	    p_proration_dates,
505     	    l_proration_change_type,
506             p_detailed_output
507         );
508         --
509     END get_event_details;
510     --
511     -- Get a flag to indicated whether or not the given table has the requested column
512     PROCEDURE get_column_flag(
513         p_table_info    IN      pay_interpreter_pkg.t_distinct_table_rec,
514         p_column        IN      VARCHAR2,
515         p_flag          IN OUT  NOCOPY VARCHAR2
516     ) IS
517         -- Find the column in the data-dictionary
518         CURSOR get_info(cp_name IN VARCHAR2,cp_column IN VARCHAR2,cp_owner IN VARCHAR2) IS
519             SELECT  'Y'
520             FROM    all_tab_columns
521             WHERE   table_name  = cp_name
522             AND     column_name = cp_column
523             AND     owner = cp_owner;
524         --
525         l_schema VARCHAR2(30);
526         --
527     BEGIN
528         l_schema := paywsdyg_pkg.get_table_owner(UPPER(p_table_info.table_name));
529         -- If we haven't already populated this flag
530         IF NVL(p_flag,'X') = 'X' THEN
531             --
532             -- Fetch from the cursor
533             OPEN get_info(
534                 UPPER(p_table_info.table_name),
535                 UPPER(p_column),
536                 UPPER(l_schema)
537             );
538             FETCH get_info INTO p_flag;
542                 p_flag := 'N';
539             --
540             -- If nothing came back then that column's not in the table we're looking at
541             IF get_info%NOTFOUND THEN
543             END IF;
544             CLOSE get_info;
545             --
546             -- Write out some debug info
547             msg('table = '||LOWER(p_table_info.table_name)||' '||LOWER(p_column)||' ? = '||p_flag);
548         END IF;
549     END get_column_flag;
550     --
551     -- Set the column flags in the dated table cache and return a copy of
552     -- the record we modified
553     PROCEDURE set_dated_table_column_flags(
554         p_idx       IN     NUMBER,
555         p_rec       IN OUT NOCOPY pay_interpreter_pkg.t_distinct_table_rec,
556         p_xrec      IN OUT NOCOPY t_dated_table_extras_rec
557     ) IS
558     BEGIN
559         -- See if there's a supervisor ID on the dated table
560         get_column_flag(
561             pay_interpreter_pkg.t_distinct_tab(p_idx),
562             'SUPERVISOR_ID',
563             g_DATED_TABLE_EXTRAS(p_idx).has_supervisor_id
564         );
565         -- See if there's a location ID on the dated table
566         get_column_flag(
567             pay_interpreter_pkg.t_distinct_tab(p_idx),
568             'LOCATION_ID',
569             g_DATED_TABLE_EXTRAS(p_idx).has_location_id
570         );
571         --
572         -- See if we've got an assignment ID (only really need one if supervisor or location is missing)
573         get_column_flag(
574             pay_interpreter_pkg.t_distinct_tab(p_idx),
575             'ASSIGNMENT_ID',
576             g_DATED_TABLE_EXTRAS(p_idx).has_assignment_id
577         );
578         --
579         -- Copy the records we updated to the return parameter
580         p_rec := pay_interpreter_pkg.t_distinct_tab(p_idx);
581         p_xrec := g_DATED_TABLE_EXTRAS(p_idx);
582         --
583     END set_dated_table_column_flags;
584     --
585     -- Build the SQL statement we'll need to use to get the supervisor and location IDs
586     -- Note that all statements must have the surrogate key ID and the effective
587     -- date bind variables, event if there're not used, so we can dynamically open the
588     -- cursor in a consistent way
589     -- This statement is cached in the t_distinct_tab record
590     PROCEDURE get_additional_select(
591         p_tab_id        IN      NUMBER,
592         p_want_location IN      BOOLEAN,
593         p_sql           IN OUT  NOCOPY VARCHAR2
594     ) IS
595         --
596         l_tab_info              pay_interpreter_pkg.t_distinct_table_rec;
597         l_tab_extra             t_dated_table_extras_rec;
598         l_used_skt              BOOLEAN := FALSE;
599         l_used_paf              BOOLEAN := FALSE;
600         l_tab_idx               NUMBER;
601         --
602     BEGIN
603         --
604         -- Find the dated table information in the cache which was
605         -- populated when we called event_group_tables in get_assignment_event_details
606         l_tab_idx := query_dated_table_cache(p_tab_id);
607         --
608         -- Check the cached info in the dated table record to see if we've already built
609         -- the SQL statement for this dated table
610         IF g_DATED_TABLE_EXTRAS(l_tab_idx).sql_statement IS NOT NULL THEN
611             msg('Reusing SQL statement from dated table cache');
612             p_sql := g_DATED_TABLE_EXTRAS(l_tab_idx).sql_statement;
613             RETURN;
614         END IF;
615         --
616         -- Set the flags indicating which columns we've got on this table and put
617         -- a copy of the cached information into l_tab_info
618         set_dated_table_column_flags(
619             l_tab_idx,
620             l_tab_info,
621             l_tab_extra
622         );
623         --
624         -- Build the SQL depending on what columns we've got
625         msg('Building SQL statement...');
626         --
627         -- Add the select list
628         p_sql := 'SELECT ';
629         --
630         -- Get the supervisor ID
631         IF l_tab_extra.has_supervisor_id = 'Y' THEN
632             -- We've got a supervisor ID in this table
633             p_sql := p_sql||'skt.supervisor_id, ';
634             msg('Got supervisor_id locally');
635             l_used_skt := TRUE;
636         ELSIF l_tab_extra.has_assignment_id = 'Y' THEN
637             -- Find it from the assignment
638             p_sql := p_sql||'paf.supervisor_id, ';
639             msg('Going to assignment for supervisor_id');
640             l_used_paf := TRUE;
641         ELSE
642             -- Can't get it
643             p_sql := p_sql||c_ALL_SUPERVISORS_ID||' supervisor_id, ';
644             msg('Can''t get supervisor_id');
645         END IF;
646         --
647         -- Get the location ID
648         IF p_want_location THEN
649             IF l_tab_extra.has_location_id = 'Y' THEN
650                 -- We've got a location ID in this table
651                 p_sql := p_sql||'skt.location_id, ';
652                 msg('Got location_id locally');
653                 l_used_skt := TRUE;
654             ELSIF l_tab_extra.has_assignment_id = 'Y' THEN
655                 -- Find it from the assignment
656                 p_sql := p_sql||'paf.location_id, ';
657                 msg('Going to assignment for location_id');
658                 l_used_paf := TRUE;
659             ELSE
660                 -- Can't get it
661                 p_sql := p_sql||c_BLANK_LOCATION_ID||' location_id, ';
665             -- Don't want it
662                 msg('Can''t get location_id');
663             END IF;
664         ELSE
666             p_sql := p_sql||c_BLANK_LOCATION_ID||' location_id, ';
667             msg('Don''t want location_id');
668         END IF;
669         --
670         -- Get the effective dates
671         IF (NOT l_used_paf) AND (NOT l_used_skt) THEN
672             p_sql := p_sql||'TRUNC(SYSDATE) effective_start_date, '||
673                             'TRUNC(SYSDATE) effective_end_date ';
674             msg('Adding default dates');
675             --
676         ELSE
677             p_sql := p_sql||'skt.'||l_tab_info.start_date_name||' effective_start_date, '||
678                             'skt.'||l_tab_info.end_date_name||' effective_end_date ';
679             msg('Using surrogate key table dates');
680             --
681         END IF;
682         --
683         -- Add the from list
684         p_sql := p_sql||'FROM ';
685         --
686         -- Which tables did we have to go to?
687         IF (NOT l_used_paf) AND (NOT l_used_skt) THEN
688             -- Didn't look at any tables
689             p_sql := p_sql||'dual ';
690             msg('No tables used');
691             --
692         ELSE
693             -- Must always join to the table to which the surrogate key relates
694             p_sql := p_sql||l_tab_info.table_name||' skt ';
695             msg('Getting info from '||LOWER(l_tab_info.table_name));
696             --
697             -- Did we also have to go back to the assignment to get anything
698             IF l_used_paf THEN
699                 p_sql := p_sql||', '||c_ASSIGNMENTS_TABLE||' paf ';
700                 msg('Also getting info from '||c_ASSIGNMENTS_TABLE);
701             END IF;
702         END IF;
703         --
704         -- Add the where clause
705         p_sql := p_sql||'WHERE ';
706         --
707         -- Which tables did we have to go to?
708         IF (NOT l_used_paf) AND (NOT l_used_skt) THEN
709             -- Didn't look at any tables
710             p_sql := p_sql||':surrogate_key IS NOT NULL '||
711 	                    'AND :effective_start_date IS NOT NULL '||
712 	                    'AND :effective_end_date IS NOT NULL ';
713             msg('Didn''t need any where clause, adding default');
714             --
715         ELSE
716             -- Always have to join to the table to which the surrogate key relates
717             p_sql := p_sql||'skt.'||l_tab_info.surrogate_key_name||' = :surrogate_key '||
718                             'AND :effective_start_date <= skt.'||l_tab_info.end_date_name||' '||
719 			    'AND :effective_end_date >= skt.'||l_tab_info.start_date_name||' ';
720             msg(
721                 'Adding where clause for '||LOWER(l_tab_info.surrogate_key_name)||', '||
722                 LOWER(l_tab_info.start_date_name)||' and '||
723                 LOWER(l_tab_info.end_date_name)||' columns'
724             );
725             --
726             -- Did we also have to go back to the assignment to get anything
727             IF l_used_paf THEN
728                 p_sql := p_sql||'AND paf.assignment_id = skt.assignment_id '||
729                                 'AND paf.effective_end_date >= skt.'||l_tab_info.start_date_name||' '||
730                                 'AND paf.effective_start_date <= skt.'||l_tab_info.end_date_name||' ';
731                 msg('Also joining to assignments table');
732                 --
733             END IF;
734         END IF;
735         --
736         -- Only include rows where the supervisor ID is set (and the location if needed)
737         IF l_tab_extra.has_supervisor_id = 'Y' THEN
738             p_sql := p_sql||'AND skt.supervisor_id IS NOT NULL ';
739             msg('Surrogate table supervisor must not be null');
740         ELSIF l_tab_extra.has_assignment_id = 'Y' THEN
741             p_sql := p_sql||'AND paf.supervisor_id IS NOT NULL ';
742             msg('Assignment table supervisor must not be null');
743         END IF;
744         --
745         IF p_want_location THEN
746             IF l_tab_extra.has_location_id = 'Y' THEN
747                 p_sql := p_sql||'AND skt.location_id IS NOT NULL ';
748                 msg('Surrogate table location_id must not be null');
749             ELSIF l_tab_extra.has_assignment_id = 'Y' THEN
750                 p_sql := p_sql||'AND paf.location_id IS NOT NULL ';
751                 msg('Assignment table location_id must not be null');
752             END IF;
753         ELSE
754             msg('Don''t care where location_id comes from, or if it''s null');
755         END IF;
756         --
757         -- Lets see the SQL statement
758         msg('Finished building statement');
759         msg('<sqlstatement>');
760         msg(p_sql);
761         msg('</sqlstatement>');
762         --
763         msg('Caching statement in record '||l_tab_idx);
764         g_DATED_TABLE_EXTRAS(l_tab_idx).sql_statement := p_sql;
765         --
766     END get_additional_select;
767     --
768     -- < PUBLIC FUNCTIONS > --------------------------------------------------
769     --
770     -- Return the "all supervisors" constant
771     FUNCTION all_supervisors_id RETURN NUMBER IS
772     BEGIN
773         RETURN c_ALL_SUPERVISORS_ID;
774     END all_supervisors_id;
775     --
776     -- Return the "blank location" constant
777     FUNCTION blank_location_id RETURN NUMBER IS
778     BEGIN
782     -- Get the event group ID based on its name and initialise the cache
779         RETURN c_BLANK_LOCATION_ID;
780     END blank_location_id;
781     --
783     PROCEDURE init_event_group_cache(p_event_group_name IN VARCHAR2) IS
784         --
785         CURSOR get_evt(p_grp IN VARCHAR2) IS
786             SELECT          event_group_id
787             FROM            pay_event_groups
788             WHERE           event_group_name = p_grp;
789         --
790     BEGIN
791 	--
792         -- Find the event group ID, raises no_data_found
793         -- if the event group name is invalid (i.e. not found)
794 	-- 2984406 - Fetch into a global ID to save repeated queries to get the ID
795         OPEN get_evt(p_event_group_name);
796         FETCH get_evt INTO g_EVENT_GROUP_ID;
797         IF get_evt%NOTFOUND THEN
798             -- Trace some debug info and raise the error
799             dbg('Event group "'||p_event_group_name||'" not found.');
800             CLOSE get_evt;
801             RAISE event_group_not_found;
802         END IF;
803         CLOSE get_evt;
804 	--
805 	-- Populate the internal package global caches to hold details of all
806         -- the dated tables that this event group uses
807         pay_interpreter_pkg.event_group_tables(g_EVENT_GROUP_ID);
808         --
809         -- Make sure we've got enough extra information records for all the
810         -- dated tables we're going to use
811         FOR i IN pay_interpreter_pkg.t_distinct_tab.FIRST .. pay_interpreter_pkg.t_distinct_tab.LAST LOOP
812             g_DATED_TABLE_EXTRAS(i).has_supervisor_id := 'X';
813             g_DATED_TABLE_EXTRAS(i).has_location_id   := 'X';
814             g_DATED_TABLE_EXTRAS(i).has_assignment_id := 'X';
815             g_DATED_TABLE_EXTRAS(i).sql_statement     := NULL;
816         END LOOP;
817         --
818     END init_event_group_cache;
819     --
820     -- < PUBLIC PROCEDURES > -------------------------------------------------
821     --
822     -- Get the event group ID based on its name
823     FUNCTION get_event_group_id(p_event_group_name IN VARCHAR2) RETURN NUMBER IS
824     BEGIN
825         IF g_EVENT_GROUP_ID IS NULL THEN
826 	    init_event_group_cache(p_event_group_name);
827 	END IF;
828 	RETURN g_EVENT_GROUP_ID;
829     END get_event_group_id;
830     --
831     -- Log a message, either using fnd_file, or hr_utility.trace
832     PROCEDURE msg(p_text IN VARCHAR2) IS
833         l_pos   NUMBER := 1;
834         l_txt   VARCHAR2(255);
835     BEGIN
836         --
837         -- Chop up the string into 250 char chunks if we're writing to the
838         -- concurrent manager log file
839         IF g_concurrent THEN
840             LOOP
841                 l_txt := SUBSTR(p_text,l_pos,c_OUTPUT_LINE_LENGTH);
842                 fnd_file.put_line(fnd_file.LOG,l_txt);
843                 --
844                 l_pos := l_pos + c_OUTPUT_LINE_LENGTH;
845                 EXIT WHEN l_pos > LENGTH(p_text);
846             END LOOP;
847         ELSE
848             -- Use the normal trace stuff
849             hr_utility.trace(p_text);
850         END IF;
851     END msg;
852     --
853     PROCEDURE dbg(p_text IN VARCHAR2) IS
854     BEGIN
855         IF g_debugging THEN
856             msg(p_text);
857         END IF;
858     END dbg;
859     --
860     -- Switch on or off client debugging.
861     PROCEDURE set_client_debugging(p_on IN BOOLEAN) IS
862     BEGIN
863         -- Stubbed out because we're not allowed to use dbms_output
864         RAISE feature_not_supported;
865     END set_client_debugging;
866     --
867     -- Replacement for the above - allow logging to concurrent manager log
868     PROCEDURE set_concurrent_logging(p_on IN BOOLEAN) IS
869     BEGIN
870         g_concurrent := p_on;
871     END set_concurrent_logging;
872     --
873     -- Switch debugging messages on
874     PROCEDURE set_debugging(p_on IN BOOLEAN) IS
875     BEGIN
876         g_debugging := p_on;
877     END set_debugging;
878     --
879     -- Process the detailed output information from an assignment event
880     PROCEDURE process_event_details(
881         p_detailed_output   IN      pay_interpreter_pkg.t_detailed_output_table_type,
882         p_proration_dates   IN      pay_interpreter_pkg.t_proration_dates_table_type,
883         p_summary_refresh   IN OUT  NOCOPY t_summary_refresh_tab_type,
884         p_location_stripe   IN      BOOLEAN DEFAULT FALSE
885     ) IS
886         --
887         -- Local variables
888         l_idx                   NUMBER;
889         --
890         -- The SQL statement we'll need to use to get the supervisor ID
891         -- and the dynamic cursor stuff
892         TYPE t_csr IS REF CURSOR;
893         --
894         l_csr                   t_csr;
895         l_sql                   VARCHAR2(2000);
896         l_supv                  NUMBER;
897         l_loct                  NUMBER;
898         l_sdt                   DATE;
899         l_edt                   DATE;
900         --
901     BEGIN
902         --
903         -- Make sure we have some detailed output and some dates
904         IF NVL(p_detailed_output.FIRST,0) < 1 AND
905            NVL(p_proration_dates.FIRST,0) < 1
906         THEN
907             msg('No detailed output supplied to process_event_details, ignoring');
908             RETURN;
912         -- and proration dates tables, if not then that's an error since we need
909         END IF;
910         --
911         -- There should be the same number of records in the detailed output
913         -- to have an effective date for each event
914         IF p_detailed_output.FIRST <> p_proration_dates.FIRST OR
915            p_detailed_output.LAST <> p_proration_dates.LAST
916         THEN
917             -- Trace some debug info and raise a custom error
918             msg('Records in detailed output don''t match those in proration dates.');
919             msg('t_detailed_output = '||p_detailed_output.FIRST||' -> '||p_detailed_output.LAST);
920             msg('t_proration_dates = '||p_proration_dates.FIRST||' -> '||p_proration_dates.LAST);
921             RAISE mismatch_when_summarizing;
922         END IF;
923         --
924         -- Process each record in the detailed output
925         FOR i IN p_detailed_output.FIRST .. p_detailed_output.LAST LOOP
926             --
927             -- Debugging information for event found
928             msg(
929                 'Processing event found at '||
930                 dec_date(p_proration_dates(i))||'/'||inc_date(p_proration_dates(i))||' on '||
931                 p_detailed_output(i).dated_table_id||' ID '||
932                 p_detailed_output(i).surrogate_key
933             );
934             --
935             -- Build the query to get the additional IDs based on the
936             -- information about the dated table that the event occurred on,
937             -- must always include the 3 bind variables; surrogate_key,
938             -- effective_start/end_date
939             get_additional_select(
940                 p_detailed_output(i).dated_table_id,
941                 p_location_stripe,
942                 l_sql
943             );
944             --
945             -- Open a cursor for the SQL we just built
946             OPEN l_csr FOR l_sql USING
947 	        p_detailed_output(i).surrogate_key,
948 		dec_date(p_proration_dates(i)),
949 		inc_date(p_proration_dates(i));
950             LOOP
951                 -- Get the IDs and bail when we run out
952                 FETCH l_csr INTO l_supv,l_loct,l_sdt,l_edt;
953                 EXIT WHEN l_csr%NOTFOUND;
954                 --
955                 -- Find the entry in the summary table
956                 --
957                 get_summary_idx(l_supv, l_loct, l_idx, p_summary_refresh);
958                 --
959                 -- The start date is the earliest out of the currently recorded effective date
960                 -- for this combination (NVL'd in case we haven't recorded anything yet) and the
961                 -- effective date of the event we're recording
962                 p_summary_refresh(l_idx).effective_start_date := LEAST(
963                     NVL(
964                         p_summary_refresh(l_idx).effective_start_date,
965                         p_proration_dates(i)
966                     ),
967                     dec_date(l_sdt)
968                 );
969                 --
970                 -- Update the end date similarly, but with the most recent of the two dates
971                 p_summary_refresh(l_idx).effective_end_date := GREATEST(
972                     NVL(
973                         p_summary_refresh(l_idx).effective_end_date,
974                         p_proration_dates(i)
975                     ),
976                     inc_date(l_edt)
977                 );
978                 --
979             END LOOP;
980             --
981             -- Done with the cursor;
982             CLOSE l_csr;
983         END LOOP;
984         --
985     END process_event_details;
986     --
987     -- Build up the SQL query for determining date-effective updates
988     FUNCTION build_csr_dt_updates(p_dtid IN NUMBER,p_dtname IN VARCHAR2,p_eeid IN NUMBER) RETURN VARCHAR2 IS
989         --
990 	-- Get a list of the columns that are in the event group and table
991         CURSOR get_columns(p_evt IN NUMBER,p_tab IN NUMBER) IS
992             SELECT column_name
993             FROM   pay_datetracked_events pde
994             WHERE  event_group_id = p_evt
995             AND    dated_table_id = p_tab
996             AND    update_type = 'U';
997         --
998         l_qry VARCHAR2(32767);
999     BEGIN
1000         l_qry := 'SELECT n.assignment_id, ';
1001 	--
1002 	IF p_dtid = p_eeid THEN
1003 	    l_qry := l_qry||'n.element_entry_id, ';
1004 	END IF;
1005 	--
1006         l_qry := l_qry||
1007 	         '       MIN(LEAST(o.effective_start_date,n.effective_start_date)) effective_start_date, '||
1008                  '       MAX(GREATEST(o.effective_start_date,n.effective_start_date)) effective_end_date '||
1009                  'FROM   '||p_dtname||' n, '||
1010                  '       '||p_dtname||' o '||
1011                  'WHERE n.assignment_id = o.assignment_id '||
1012                  'AND n.effective_start_date = o.effective_end_date + 1 '||
1013                  'AND (';
1014         --
1015         FOR col_rec IN get_columns(g_EVENT_GROUP_ID,p_dtid) LOOP
1016             IF get_columns%rowcount > 1 THEN
1017                 l_qry := l_qry||' OR ';
1018             END IF;
1019             --
1020             l_qry := l_qry||'NVL(TO_CHAR(o.'||col_rec.column_name||'), ''$Sys_Def$'') <> '||
1021                             'NVL(TO_CHAR(n.'||col_rec.column_name||'), ''$Sys_Def$'')';
1022             --
1023         END LOOP;
1027 		     'SELECT '||
1024         --
1025         l_qry := l_qry ||') '||
1026 	             'AND n.assignment_id IN ('||
1028 		     '    ppe.assignment_id '||
1029 		     '    FROM pay_process_events ppe,pay_event_updates peu '||
1030 		     '    WHERE ppe.creation_date BETWEEN :1 AND :2 '||
1031 		     '    AND peu.event_update_id = ppe.event_update_id '||
1032 		     '    AND peu.dated_table_id = '||p_dtid||
1033 		    ') '||
1034                     'GROUP BY n.assignment_id';
1035 	IF p_dtid = p_eeid THEN
1036 	    l_qry := l_qry||',n.element_entry_id';
1037 	END IF;
1038 	--
1039 	RETURN l_qry;
1040     END build_csr_dt_updates;
1041     --
1042     FUNCTION get_element_entry_table_id RETURN NUMBER IS
1043         l_element_entries_dt_id NUMBER;
1044     BEGIN
1045     	--
1046 	-- Get the (special case) element entries table ID
1047 	BEGIN
1048 	    SELECT  dated_table_id
1049 	    INTO    l_element_entries_dt_id
1050 	    FROM    pay_dated_tables
1051 	    WHERE   table_name = 'PAY_ELEMENT_ENTRIES_F';
1052 	EXCEPTION
1053 	    WHEN OTHERS THEN l_element_entries_dt_id := NULL;
1054 	END;
1055 	RETURN l_element_entries_dt_id;
1056     END get_element_entry_table_id;
1057 --
1058     --
1059     -- Is the Entry Id supplied a Salary Element
1060     --
1061     FUNCTION is_salary(p_ee_id in number)
1062     RETURN BOOLEAN IS
1063       l_dummy number;
1064     BEGIN
1065 --
1066        select /*+ ordered */ distinct pee.element_entry_id
1067          into l_dummy
1068          from pay_element_entries_f    pee,
1069               per_all_assignments_f    paf,
1070               per_pay_bases            ppb,
1071               pay_element_entry_values_f peev
1072         where pee.element_entry_id = p_ee_id
1073           and pee.assignment_id = paf.assignment_id
1074           and paf.pay_basis_id = ppb.pay_basis_id
1075           and pee.element_entry_id = peev.element_entry_id
1076           and ppb.input_value_id = peev.input_value_id;
1077 --
1078          return TRUE;
1079 --
1080     EXCEPTION
1081          when no_data_found then
1082             return FALSE;
1083 --
1084     END is_salary;
1085     --
1086     -- Get a list of the assignments that have events recorded for them.
1087     -- Bug 2984406: Restructure to fetch affected assignments in three stages,
1088     -- basically changes the whole structure of this procedure
1089     PROCEDURE get_assignments_affected(
1090         p_start_date        IN      DATE,
1091         p_end_date          IN      DATE,
1092         p_assignments       IN OUT  NOCOPY t_assignment_id_tab_type
1093     ) IS
1094         --
1095         l_csr 				csr_dyn_ref;
1096         l_qry 				VARCHAR2(32767);
1097 	l_assignment_id 		NUMBER;
1098 	l_element_entry_id 		NUMBER;
1099 	l_effective_start_date 		DATE;
1100 	l_effective_end_date 		DATE;
1101 	l_element_entries_dt_id 	NUMBER;
1102 	--
1103         l_loop NUMBER;
1104         curr_ass_id NUMBER;
1105         new_assignment BOOLEAN;
1106         --
1107     BEGIN
1108         -- Get the affected assignments
1109         msg('Getting affected assignments for '||fnd_date.date_to_canonical(p_start_date)||' '||fnd_date.date_to_canonical(p_end_date));
1110         l_loop := 0;
1111         l_element_entries_dt_id := get_element_entry_table_id;
1112 	--
1113 	-- Get those affected by inserts and deletes
1114 	msg('Getting inserts and deletes');
1115         curr_ass_id := -1;
1116         FOR assrec in csr_all_changes(p_start_date,p_end_date) loop
1117 --
1118             if(curr_ass_id <> assrec.assignment_id) then
1119                curr_ass_id := assrec.assignment_id;
1120                new_assignment := TRUE;
1121             end if;
1122 --
1123             /* If the table is element entries then we need to do some thing */
1124             if assrec.dated_table_id = l_element_entries_dt_id then
1125 --
1126                   if( is_salary(assrec.surrogate_key) = TRUE) then
1127 --
1128                     /* It is salary, here comes the tricky part
1129                     */
1130                     if (new_assignment = TRUE) then
1131                       l_loop := l_loop + 1;
1132                       p_assignments(l_loop).element_entry_id
1133                                     := assrec.surrogate_key;
1134                       p_assignments(l_loop).assignment_id
1135                                     := assrec.assignment_id;
1136                       p_assignments(l_loop).effective_start_date
1137                                     := dec_date(assrec.effective_start_date);
1138                       p_assignments(l_loop).effective_end_date
1139                                     := inc_date(assrec.effective_end_date);
1140                       new_assignment := FALSE;
1141                     else
1142                       if (p_assignments(l_loop).element_entry_id is null) then
1143                          p_assignments(l_loop).element_entry_id
1144                            := assrec.surrogate_key;
1145                          p_assignments(l_loop).effective_start_date
1146                            := least(p_assignments(l_loop).effective_start_date,
1147                                     dec_date(assrec.effective_start_date));
1148                          p_assignments(l_loop).effective_end_date
1149                            := greatest(p_assignments(l_loop).effective_end_date,
1153                          l_loop := l_loop + 1;
1150                                        inc_date(assrec.effective_end_date));
1151                       else
1152                          /* Yeah we really need to create a new one */
1154                          p_assignments(l_loop).element_entry_id
1155                                        := assrec.surrogate_key;
1156                          p_assignments(l_loop).assignment_id
1157                                        := assrec.assignment_id;
1158                          p_assignments(l_loop).effective_start_date
1159                                        := dec_date(assrec.effective_start_date);
1160                          p_assignments(l_loop).effective_end_date
1161                                        := inc_date(assrec.effective_end_date);
1162                       end if;
1163                     end if;
1164 --
1165                   else
1166                      /* do nothing it's not salary, hence
1167                         not interested
1168                      */
1169                      null;
1170                   end if;
1171 --
1172             else
1173                 /* It's not an element entry change.
1174                    Check that a row has not already been placed
1175                    in the pl/sql table for this assignment
1176                    If it has just adjust the dates.
1177                 */
1178                 if (new_assignment = TRUE) then
1179                    l_loop := l_loop + 1;
1180                    p_assignments(l_loop).element_entry_id := NULL;
1181                    p_assignments(l_loop).assignment_id
1182                                  := assrec.assignment_id;
1183                    p_assignments(l_loop).effective_start_date
1184                                  := dec_date(assrec.effective_start_date);
1185                    p_assignments(l_loop).effective_end_date
1186                                  := inc_date(assrec.effective_end_date);
1187                    new_assignment := FALSE;
1188                 else
1189                    p_assignments(l_loop).effective_start_date
1190                        := least(p_assignments(l_loop).effective_start_date,
1191                                 dec_date(assrec.effective_start_date));
1192                    p_assignments(l_loop).effective_end_date
1193                        := greatest(p_assignments(l_loop).effective_end_date,
1194                                    inc_date(assrec.effective_end_date));
1195                 end if;
1196             end if;
1197         END LOOP;
1198         --
1199         IF NVL(p_assignments.FIRST,0) < 1 THEN
1200             msg('No assignment events found within specified date range');
1201             RAISE no_assignment_events_found;
1202         END IF;
1203         --
1204     END get_assignments_affected;
1205     --
1206     -- Get the payroll event details based on a list of assignment IDs
1207     PROCEDURE get_refresh_periods(
1208         p_assignments       IN OUT  NOCOPY t_assignment_id_tab_type,
1209         p_summary_refresh   IN OUT  NOCOPY t_summary_refresh_tab_type,
1210         p_start_date        IN      DATE,
1211         p_end_date          IN      DATE,
1212         p_location_stripe   IN      BOOLEAN DEFAULT FALSE
1213     ) IS
1214         --
1215         -- Local table-type variables for use with processing the event details
1216         l_detailed_output       pay_interpreter_pkg.t_detailed_output_table_type;
1217         l_proration_dates       pay_interpreter_pkg.t_proration_dates_table_type;
1218         --
1219     BEGIN
1220         --
1221         -- Check we've got something to process
1222         IF NVL(p_assignments.FIRST,0) < 1 THEN
1223             msg('No data from process in get_assignment_events');
1224             RAISE no_assignments_supplied;
1225         END IF;
1226         --
1227         -- Process all the assignments we got
1228         FOR i IN p_assignments.FIRST .. p_assignments.LAST LOOP
1229 --
1230             l_detailed_output.delete;
1231             l_proration_dates.delete;
1232             --
1233             -- Get the detailed event information for this assignment
1234             get_event_details(
1235                 p_start_date,
1236                 p_end_date,
1237                 p_assignments(i).assignment_id,
1238 		p_assignments(i).element_entry_id,
1239                 l_detailed_output,
1240                 l_proration_dates
1241             );
1242             --
1243             -- Process the event details for this assignment
1244             -- (a check is done within this procedure for the detailed output being empty)
1245             msg(
1246                 'Processing event details ('||
1247                 p_assignments(i).assignment_id||' '||
1248                 p_assignments(i).effective_start_date||' -> '||
1249                 p_assignments(i).effective_end_date||')'
1250             );
1251             process_event_details(
1252                 l_detailed_output,
1253                 l_proration_dates,
1254                 p_summary_refresh,
1255                 p_location_stripe
1256             );
1257         END LOOP;
1258     END get_refresh_periods;
1259     --
1260     -- If we recorded some information for "all records" (i.e. an event ocurred on a
1261     -- table which didn't allow us to get a proper supervisor or location ID)
1262     -- then we need to delete any specific records that fall completely within
1266         p_summary_refresh_temp  IN OUT NOCOPY t_summary_refresh_tab_type,
1263     -- "refresh all" period, and chop up any records that just overlap that period, otherwise
1264     -- we'll just copy the temporary table to the output parameter
1265     PROCEDURE de_dupe_refresh_periods(
1267         p_summary_refresh       IN OUT NOCOPY t_summary_refresh_tab_type,
1268         p_all_supv              IN OUT NOCOPY BOOLEAN,
1269         p_out_num               IN OUT NOCOPY NUMBER,
1270         p_all_start             IN OUT NOCOPY DATE,
1271         p_all_end               IN OUT NOCOPY DATE,
1272         p_want_location         IN     BOOLEAN DEFAULT FALSE
1273     ) IS
1274     BEGIN
1275         p_all_supv := FALSE;
1276         p_out_num  := 0;
1277         --
1278         IF NVL(p_summary_refresh_temp.FIRST,0) > 0 THEN
1279             --
1280             -- Find the "all" record
1281             FOR i IN p_summary_refresh_temp.FIRST .. p_summary_refresh_temp.LAST LOOP
1282                 IF p_summary_refresh_temp(i).supervisor_id = c_ALL_SUPERVISORS_ID OR
1283                    (p_summary_refresh_temp(i).location_id = c_BLANK_LOCATION_ID AND p_want_location)
1284                 THEN
1285                     p_all_start := p_summary_refresh(i).effective_start_date;
1286                     p_all_end := p_summary_refresh(i).effective_end_date;
1287                     p_all_supv := TRUE;
1288                 END IF;
1289             END LOOP;
1290             --
1291             IF p_all_supv THEN
1292                 --
1293                 -- If either the start or end date is null then bail
1294                 IF p_all_start IS NULL OR p_all_end IS NULL THEN
1295                     msg('An "all" record was missing one or other of the required dates');
1296                     RAISE missing_dates_in_all_record;
1297                 END IF;
1298                 --
1299                 -- Record the "all" record
1300                 p_out_num := p_out_num + 1;
1301                 p_summary_refresh(p_out_num).supervisor_id := c_ALL_SUPERVISORS_ID;
1302                 p_summary_refresh(p_out_num).location_id := c_BLANK_LOCATION_ID;
1303                 p_summary_refresh(p_out_num).effective_start_date := p_all_start;
1304                 p_summary_refresh(p_out_num).effective_end_date := p_all_end;
1305                 --
1306                 -- Go through the other records (skipping the "all" one) and chopping the dates
1307                 FOR i IN p_summary_refresh_temp.FIRST .. p_summary_refresh_temp.LAST LOOP
1308                     IF p_summary_refresh_temp(i).supervisor_id <> c_ALL_SUPERVISORS_ID AND
1309                        (p_summary_refresh_temp(i).location_id <> c_BLANK_LOCATION_ID OR (NOT p_want_location))
1310                     THEN
1311                         --
1312                         -- If either the start or end date is null then bail
1313                         IF p_summary_refresh_temp(i).effective_start_date IS NULL OR
1314                            p_summary_refresh_temp(i).effective_end_date IS NULL
1315                         THEN
1316                             msg(
1317                                 'A specific ('||p_summary_refresh_temp(i).supervisor_id||
1318                                 '/'||p_summary_refresh_temp(i).location_id||
1319                                 ') refresh record is missing a start or end date'
1320                             );
1321                             RAISE missing_dates_for_specific;
1322                         END IF;
1323                         --
1324                         -- If the specific refresh record falls completely within the "all"
1325                         -- period the don't process it
1326                         IF p_summary_refresh_temp(i).effective_start_date >= p_all_start AND
1327                            p_summary_refresh_temp(i).effective_end_date <= p_all_end
1328                         THEN
1329                             msg(
1330                                 'Specific '||p_summary_refresh_temp(i).supervisor_id||
1331                                 '/'||p_summary_refresh_temp(i).location_id||
1332                                 ' falls entirely within "all" refresh period, ignoring.'
1333                             );
1334                         ELSE
1335                             -- If this record starts before the "all" period then record a segment
1336                             IF p_summary_refresh_temp(i).effective_start_date < p_all_start THEN
1337                                 msg(
1338                                     'Specific '||p_summary_refresh_temp(i).supervisor_id||
1339                                     '/'||p_summary_refresh_temp(i).location_id||
1340                                     ' starts before the "all" refresh period, processing.'
1341                                 );
1342                                 --
1343                                 p_out_num := p_out_num + 1;
1344                                 p_summary_refresh(p_out_num) := p_summary_refresh_temp(i);
1345                                 p_summary_refresh(p_out_num).effective_end_date := p_all_start - 1;
1346                             END IF;
1347                             --
1348                             -- If this record end after the "all" period then record a segment
1349                             IF p_summary_refresh_temp(i).effective_end_date > p_all_end THEN
1350                                 msg(
1351                                     'Specific '||p_summary_refresh_temp(i).supervisor_id||
1352                                     '/'||p_summary_refresh_temp(i).location_id||
1353                                     ' ends after the "all" refresh period, processing.'
1354                                 );
1355                                 --
1359                             END IF;
1356                                 p_out_num := p_out_num + 1;
1357                                 p_summary_refresh(p_out_num) := p_summary_refresh_temp(i);
1358                                 p_summary_refresh(p_out_num).effective_start_date := p_all_end + 1;
1360                         END IF;
1361                     END IF;
1362                 END LOOP;
1363                 --
1364             ELSE
1365                 -- No "all" period, just copy everything to the output parameter
1366                 FOR i IN p_summary_refresh_temp.FIRST .. p_summary_refresh_temp.LAST LOOP
1367                     --
1368                     -- If either the start or end date is null then bail
1369                     IF p_summary_refresh_temp(i).effective_start_date IS NULL OR
1370                        p_summary_refresh_temp(i).effective_end_date IS NULL
1371                     THEN
1372                         msg('A specific ('||
1373                             p_summary_refresh_temp(i).supervisor_id||'/'||
1374                             p_summary_refresh_temp(i).location_id||
1375                             ') refresh record is missing a start or end date'
1376                         );
1377                         RAISE missing_dates_for_specific;
1378                     END IF;
1379                     --
1380                     p_out_num := p_out_num + 1;
1381                     p_summary_refresh(p_out_num) := p_summary_refresh_temp(i);
1382                 END LOOP;
1383             END IF;
1384         END IF;
1385         --
1386     END de_dupe_refresh_periods;
1387     --
1388     -- Add a record to the refresh table, as long as it's not there already
1389     PROCEDURE add_summary_refresh_record(
1390         p_idx                IN OUT NOCOPY NUMBER,
1391         p_table              IN OUT NOCOPY t_summary_refresh_tab_type,
1392         p_supervisor         IN     NUMBER,
1393         p_start_date         IN     DATE,
1394         p_end_date           IN     DATE,
1395         p_location           IN     NUMBER,
1396         p_update_mode        IN     BOOLEAN
1397     ) IS
1398         l_found     NUMBER := -1;
1399     BEGIN
1400         --
1401         get_summary_idx(p_supervisor, p_location, p_idx, p_table);
1402         --
1403         p_table(p_idx).effective_start_date :=
1404                           LEAST(dec_date(p_start_date),
1405                                 nvl(p_table(p_idx).effective_start_date,
1406                                     p_start_date));
1407         p_table(p_idx).effective_end_date :=
1408                           GREATEST(inc_date(p_end_date),
1409                                    nvl(p_table(p_idx).effective_end_date,
1410                                        p_end_date));
1411         --
1412     END add_summary_refresh_record;
1413     --
1414     -- Add any date track corrections to supervisor ID on per_all_assignments_f
1415     -- if we've got that column in our event group
1416     PROCEDURE add_supervisor_corrections(
1417         p_summary_refresh   IN OUT  NOCOPY t_summary_refresh_tab_type,
1418         p_start_date        IN      DATE,
1419         p_end_date          IN      DATE,
1420         p_location_stripe   IN      BOOLEAN DEFAULT FALSE
1421     ) IS
1422         --
1423         l_start                 NUMBER      := NVL(p_summary_refresh.LAST,0) + 1;
1424         l_idx                   NUMBER      := l_start;
1425         l_end                   NUMBER;
1426         l_stripe                VARCHAR2(1) := 'N';
1427         --
1428     BEGIN
1429         msg('Adding supervisor ID correction changes');
1430         dbg('Start index is at row '||l_idx);
1431         dbg('Parameters are (not including output table):');
1432         dbg('p_start_date => '||fnd_date.date_to_canonical(p_start_date));
1433         dbg('p_end_date => '||fnd_date.date_to_canonical(p_end_date));
1434         --
1435         dbg('g_EVENT_GROUP_ID => '||g_EVENT_GROUP_ID);
1436         --
1437         -- Switch on location striping if desired
1438         IF p_location_stripe THEN
1439             dbg('Switching on location striping');
1440             l_stripe := 'Y';
1441         END IF;
1442         dbg('p_location_stripe => '||l_stripe);
1443         --
1444         -- Get all supervisor ID changes and add them to the list of refresh periods
1445         FOR l_rec IN csr_supv_corrections(
1446             g_EVENT_GROUP_ID,
1447             p_start_date,
1448             p_end_date,
1449             l_stripe
1450         ) LOOP
1451             add_summary_refresh_record(
1452                 l_idx,
1453                 p_summary_refresh,
1454                 l_rec.assignment_or_supervisor_id,
1455                 l_rec.effective_start_date,
1456                 l_rec.effective_end_date,
1457                 l_rec.table_or_location_id,
1458                 p_update_mode => FALSE
1459             );
1460         END LOOP;
1461         --
1462         -- Make sure we added some rows to the table, this isn't a fatal exception
1463         -- yet 'cos we could already have something in the table
1464         l_end := NVL(p_summary_refresh.LAST,0) + 1;
1465         dbg('End index is now at row '||l_end);
1466         IF l_start = l_end THEN
1467             RAISE no_supervisor_corrections;
1468         END IF;
1469         --
1470     END add_supervisor_corrections;
1471     --
1472     -- Get the list of supervisors and the date range across which
1473     -- each of those supervisors should be refreshed.
1477         p_end_date        IN     DATE,
1474     PROCEDURE get_summaries_affected(
1475         p_event_group     IN     VARCHAR2,
1476         p_start_date      IN     DATE,
1478         p_summary_refresh IN OUT NOCOPY t_summary_refresh_tab_type,
1479         p_location_stripe IN     BOOLEAN DEFAULT FALSE,
1480         p_raise_no_data   IN     BOOLEAN DEFAULT FALSE
1481     ) IS
1482         --
1483         -- A list of assignments that events have ocurred for
1484         l_assignments           t_assignment_id_tab_type;
1485         --
1486         -- Temporary table to store the results in, before we post-process it
1487         -- to handle "all supervisor refresh" events
1488         l_summary_refresh_temp  t_summary_refresh_tab_type;
1489         --
1490         -- Parameters used to process the "all supervisor refresh" events
1491         l_all_supv              BOOLEAN;
1492         l_out_num               NUMBER;
1493         l_all_start             DATE;
1494         l_all_end               DATE;
1495         --
1496         -- Profiling (timing) variables
1497         l_start                 NUMBER;
1498 	l_curr                  NUMBER;
1499         --
1500     BEGIN
1501         --
1502         dbg('Running get_summaries_affected, parameters;');
1503         dbg('p_event_group => '||p_event_group);
1504         dbg('p_start_date => '||p_start_date);
1505         dbg('p_end_date => '||p_end_date);
1506         IF p_location_stripe THEN
1507             dbg('p_location_stripe => TRUE');
1508         ELSE
1509             dbg('p_location_stripe => FALSE');
1510         END IF;
1511         IF p_raise_no_data THEN
1512             dbg('p_raise_no_data => TRUE');
1513         ELSE
1514             dbg('p_raise_no_data => FALSE');
1515         END IF;
1516         --
1517         -- Get the current time (100th's of a second)
1518         l_start := dbms_utility.get_time;
1519         g_SECONDS_ELAPSED := 0;
1520         --
1521         -- Clear out the results table, and the event group cache
1522         p_summary_refresh.DELETE;
1523 	g_DATED_TABLE_EXTRAS.DELETE;
1524 	g_EVENT_GROUP_ID := NULL;
1525 	--
1526 	-- Initialise the events group cache
1527 	-- 2984406: Moved to here, instead of on a per-assignment basis
1528 	init_event_group_cache(p_event_group);
1529         --
1530         BEGIN
1531             --
1532             -- Get all the assignment IDs for which events
1533             -- have occurred, but ignore supervisor ID changes
1534             get_assignments_affected(
1535                 p_start_date,
1536                 p_end_date,
1537                 l_assignments
1538             );
1539             --
1540             -- Process all the assignments we found
1541             get_refresh_periods(
1542                 l_assignments,
1543                 l_summary_refresh_temp,
1544                 p_start_date,
1545                 p_end_date,
1546                 p_location_stripe
1547             );
1548         EXCEPTION WHEN no_assignment_events_found THEN
1549             msg('No affected assignments were found in the refresh period');
1550         END;
1551         --
1552         BEGIN
1553             --
1554             -- Add the refresh periods for changes to the supervisor ID column
1555             add_supervisor_corrections(
1556                 l_summary_refresh_temp,
1557                 p_start_date,
1558                 p_end_date,
1559                 p_location_stripe
1560             );
1561         EXCEPTION WHEN no_supervisor_corrections THEN
1562             msg('No datetrack corrections to supervisor ID were found within refresh period');
1563         END;
1564         --
1565         -- Check that we've got something in the summary refresh table
1566         IF NVL(l_summary_refresh_temp.LAST,0) <= 0 THEN
1567             msg('No records in refresh table, nothing to do');
1568             dbg('Finished get_summaries_affected');
1569 	    --
1570 	    -- Record the time taken (to get nothing!)
1571 	    l_curr := dbms_utility.get_time;
1572             g_SECONDS_ELAPSED := (l_curr - l_start) / 100;
1573             msg(get_elapsed_time_text);
1574             --
1575 	    -- Clear the looping globals
1576 	    g_FIRST_RECORD := 0;
1577 	    g_LAST_RECORD := 0;
1578     	    g_CURRENT_RECORD := 0;
1579 	    --
1580             RETURN;
1581         END IF;
1582         --
1583         -- De-duplicate the records, what this means is that we remove any
1584         -- portions of refresh records for specific supervisors that overlap
1585         -- the "all" period. This period will always be contiguous, after the
1586         -- de-dupe process the specific supervisor records may not be.
1587         de_dupe_refresh_periods(
1588             l_summary_refresh_temp,
1589             p_summary_refresh,
1590             l_all_supv,
1591             l_out_num,
1592             l_all_start,
1593             l_all_end
1594         );
1595         --
1596         -- We've finished. Record some diagnostics trace information
1597         msg('Supervisor refresh events recorded: '||l_out_num);
1598         IF NOT l_all_supv THEN
1599             msg('There is no "refresh all" period');
1600         ELSE
1601             msg('Refresh all supervisors for: '||l_all_start||' -> '||l_all_end);
1602         END IF;
1603 	--
1604 	-- Record the time taken for the full run
1605 	l_curr := dbms_utility.get_time;
1606         g_SECONDS_ELAPSED := (l_curr - l_start) / 100;
1607         msg(get_elapsed_time_text);
1608         --
1612 	g_CURRENT_RECORD := 0;
1609 	-- Initialise the globals we use for simplified record looping
1610 	g_FIRST_RECORD := NVL(p_summary_refresh.FIRST,0);
1611 	g_LAST_RECORD := NVL(p_summary_refresh.LAST,0);
1613         --
1614         -- If we asked then raise no_data_found if there's no data in the table
1615         dbg('Finished get_summaries_affected');
1616         IF p_raise_no_data THEN
1617             IF NVL(p_summary_refresh.FIRST,0) <= 0 THEN
1618                 RAISE no_data_found;
1619             END IF;
1620         END IF;
1621     END get_summaries_affected;
1622     --
1623     FUNCTION next_record RETURN BOOLEAN IS
1624     BEGIN
1625         g_CURRENT_RECORD := g_CURRENT_RECORD + 1;
1626 	RETURN (g_CURRENT_RECORD >= g_FIRST_RECORD AND g_CURRENT_RECORD <= g_LAST_RECORD);
1627     END next_record;
1628     --
1629     FUNCTION current_record RETURN NUMBER IS
1630     BEGIN
1631         RETURN LEAST(g_CURRENT_RECORD,g_LAST_RECORD + 1);
1632     END current_record;
1633     --
1634 END pay_events_wrapper;