DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_DBI_WMV_SEPARATION

Source


1 PACKAGE BODY hri_dbi_wmv_separation AS
2 /* $Header: hridbite.pkb 115.21 2003/06/17 23:57:49 exjones noship $ */
3     --
4     -- ***********************************************************************
5     -- * Private globals and types                                           *
6     -- ***********************************************************************
7     --
8     -- Cache separations against subordinates (inc. direct reports)
9     TYPE t_subord_cache_rec IS RECORD(
10         subordinate_id          NUMBER,
11         voluntary_seps          NUMBER,
12         involuntary_seps        NUMBER
13     );
14     TYPE t_subord_cache_table IS
15         TABLE OF t_subord_cache_rec
16         INDEX BY BINARY_INTEGER;
17     --
18     -- Cache subordinate rows against supervisors
19     TYPE t_supv_cache_rec IS RECORD(
20         supervisor_id       NUMBER,
21         subordinate_rows    t_subord_cache_table
22     );
23     TYPE t_supv_cache_table IS
24         TABLE OF t_supv_cache_rec
25         INDEX BY BINARY_INTEGER;
26     --
27     -- Cache all supervisor separations against effective dates
28     TYPE t_effdt_cache_rec IS RECORD(
29         effective_date      DATE,
30         supervisor_rows     t_supv_cache_table
31     );
32     TYPE t_effdt_cache_table IS
33         TABLE OF t_effdt_cache_rec
34         INDEX BY BINARY_INTEGER;
35     --
36     -- Global setup variables
37     g_appl_err              CONSTANT NUMBER       := -20000;
38     g_direct_insert         CONSTANT BOOLEAN      := FALSE;
39     g_debugging                      BOOLEAN;
40     g_concurrent                     BOOLEAN;
41     --
42     -- Globals for who columns
43     g_who_id                         NUMBER;
44     g_who_date                       DATE;
45     g_who_version                    NUMBER;
46     g_who_login                      NUMBER;
47     g_who_request                    NUMBER;
48     g_who_application                NUMBER;
49     g_who_program                    NUMBER;
50     --
51     -- Global workforce measurement type
52     g_global_wmt                     VARCHAR2(30);
53     --
54     -- Globals for messages to output to the logs
55     g_success_message                VARCHAR2(2000);
56     g_failure_message                VARCHAR2(2000);
57     g_start_full_msg                 VARCHAR2(2000);
58     g_start_delta_msg                VARCHAR2(2000);
59     g_setup_failure                  VARCHAR2(2000);
60     --
61     -- Cache all inserts to save us going back and forth to the summary table
62     g_insert_cache                   t_effdt_cache_table;
63     --
64     -- Shared cursor to traverse up the supervisor hierarchy
65     CURSOR get_supsup(
66         cp_sup_id   IN NUMBER,
67         cp_eff_dt   IN DATE
68     ) IS
69         SELECT    sup_person_id,
70                   sub_relative_level,
71                   0 row_number
72         FROM      hri_cs_suph_v
73         WHERE     sub_person_id = cp_sup_id
74         AND       sub_relative_level > 0
75         AND       cp_eff_dt BETWEEN effective_start_date AND effective_end_date
76         ORDER BY  sub_relative_level ASC;
77     --
78     -- ***********************************************************************
79     -- * Get the global WMT we're going to use                               *
80     -- ***********************************************************************
81     FUNCTION global_wmt RETURN VARCHAR2 IS
82     BEGIN
83         RETURN g_global_wmt;
84     END global_wmt;
85     --
86     -- ***********************************************************************
87     -- * Log a message using the BIS refresh framework logging routine       *
88     -- ***********************************************************************
89     PROCEDURE msg(p_msg IN VARCHAR2) IS
90     BEGIN
91         IF g_concurrent THEN
92             bis_collection_utilities.log(p_msg,0);
93         ELSE
94             hr_utility.trace(p_msg);
95         END IF;
96     END msg;
97     --
98     PROCEDURE dbg(p_msg IN VARCHAR2) IS
99     BEGIN
100         IF g_debugging THEN
101             msg(p_msg);
102         END IF;
103     END dbg;
104     --
105     PROCEDURE set_debugging(p_on IN BOOLEAN) IS
106     BEGIN
107         g_debugging := p_on;
108     END set_debugging;
109     --
110     PROCEDURE set_concurrent_logging(p_on IN BOOLEAN) IS
111     BEGIN
112         g_concurrent := p_on;
113     END set_concurrent_logging;
114     --
115     -- ***********************************************************************
116     -- * Initialise all the global values                                    *
117     -- ***********************************************************************
118     PROCEDURE initialise_globals IS
119     BEGIN
120         g_who_id          := fnd_global.user_id;
121         g_who_date        := TRUNC(SYSDATE);
122         g_who_version     := 1;
123         g_who_login       := fnd_global.conc_login_id;
124         g_who_request     := fnd_global.conc_request_id;
125         g_who_application := fnd_global.prog_appl_id;
126         g_who_program     := fnd_global.conc_program_id;
127         --
128         g_global_wmt      := bis_common_parameters.get_workforce_mes_type_id;
129         --
130         g_start_full_msg  := 'Begin summary refresh full update run...';
131         g_start_delta_msg := 'Begin summary refresh delta update run...';
132         g_success_message := 'Refresh run completed successfully.';
133         g_failure_message := 'Refresh run failed: ';
134         g_setup_failure   := 'A failure occurred using the BIS run setup routine.';
135         --
136         g_debugging       := FALSE;
137         g_concurrent      := TRUE;
138         --
139     END initialise_globals;
140     --
141     -- ***********************************************************************
142     -- * Build the table of refresh records in exactly the same format as is *
143     -- * returned from the payroll events wrapper, but based on the          *
144     -- * effective dates rather than actual calendar dates                   *
145     -- * Also deletes all appropriate records from the summary table         *
146     -- ***********************************************************************
147     PROCEDURE build_full_refresh_table(
148         p_supv_tab      IN OUT NOCOPY pay_events_wrapper.t_summary_refresh_tab_type,
149         p_start_date    IN      DATE,
150         p_end_date      IN      DATE
151     ) IS
152         --
153         -- Get a list of supervisors for which terminations have occurred
154         -- between the dates specified, and the effective dates of those terminations
155         CURSOR get_supervisors_affected(
156             cp_start    IN      DATE,
157             cp_end      IN      DATE
158         ) IS
159             SELECT  asg.supervisor_id                    supervisor_id,
160                     MIN(pos.actual_termination_date-1)   effective_start_date,
161                     MAX(pos.actual_termination_date+1)   effective_end_date
162             FROM per_all_assignments_f     asg
163                , per_periods_of_service    pos
164             WHERE asg.supervisor_id IS NOT NULL
165             AND asg.period_of_service_id = pos.period_of_service_id
166             AND pos.actual_termination_date <= TRUNC(SYSDATE)
167             AND asg.effective_end_date = pos.actual_termination_date
168             AND pos.actual_termination_date BETWEEN cp_start AND cp_end
169             GROUP BY asg.supervisor_id;
170         --
171         l_recs NUMBER;
172         l_sql_stmt         VARCHAR2(500);
173         l_dummy1           VARCHAR2(2000);
174         l_dummy2           VARCHAR2(2000);
175         l_schema           VARCHAR2(400);
176         --
177     BEGIN
178         --
179         -- Get all the supervisors for which separations have occurred
180         -- within the date range specified
181         msg('Finding all separations affected supervisors between '||p_start_date||' and '||p_end_date);
182         l_recs := 0;
183         FOR rec_supv IN get_supervisors_affected(p_start_date,p_end_date) LOOP
184             l_recs := l_recs + 1;
185             dbg('Supervisor('||l_recs||'): '||rec_supv.supervisor_id);
186             p_supv_tab(l_recs).supervisor_id         := rec_supv.supervisor_id;
187             p_supv_tab(l_recs).location_id           := pay_events_wrapper.blank_location_id;
188             p_supv_tab(l_recs).effective_start_date  := rec_supv.effective_start_date;
189             p_supv_tab(l_recs).effective_end_date    := rec_supv.effective_end_date;
190         END LOOP;
191         msg('Found '||NVL((p_supv_tab.LAST - p_supv_tab.FIRST)+1,0)||' ('||l_recs||') records');
192         --
193         -- Delete all our records from the summary table, regardless of
194         -- dates and supervisors since this is a full refresh
195         msg('Deleting all existing summary rows');
196         IF (fnd_installation.get_app_info('PER',l_dummy1, l_dummy2, l_schema)) THEN
197 
198             l_sql_stmt := 'ALTER TABLE '|| l_schema ||'.HR_PTL_SUMMARY_DATA TRUNCATE PARTITION ' ||
199                            information_category;
200             EXECUTE IMMEDIATE(l_sql_stmt);
201         END IF;
202         --
203         msg('Deleted all rows');
204         --
205     END build_full_refresh_table;
206     --
207     -- ***********************************************************************
208     -- * Use the payroll events model wrapper to build the table of          *
209     -- * supervisors that we need to refresh                                 *
210     -- * Also deletes all appropriate records from the summary table         *
211     -- ***********************************************************************
212     PROCEDURE build_delta_refresh_table(
213         p_supv_tab      IN OUT NOCOPY pay_events_wrapper.t_summary_refresh_tab_type,
214         p_start_date    IN      DATE,
215         p_end_date      IN      DATE
216     ) IS
217         --
218         CURSOR get_deletes_todo(
219             cp_id       IN NUMBER,
220             cp_st       IN DATE,
221             cp_en       IN DATE
222         ) IS
223             SELECT  summary_context_id  supervisor_id,
224                     effective_date,
225                     sum_information4 voluntary_char,
226                     sum_information5 involuntary_char
227             FROM    hr_ptl_summary_data
228             WHERE   effective_date BETWEEN cp_st AND cp_en
229             AND     summary_context_id = cp_id
230             AND     sum_information_category = information_category;
231         --
232         l_sub_id      NUMBER;
233         l_loop        NUMBER;
234         --
235     BEGIN
236         --
237         -- Use the payroll events model to calculate the supervisors and
238         -- date ranges that we need to recalculate
239         msg('Getting affected supervisors from Payroll Events Model wrapper');
240         pay_events_wrapper.get_summaries_affected(
241             p_event_group     => event_group,
242             p_start_date      => p_start_date,
243             p_end_date        => p_end_date,
244             p_summary_refresh => p_supv_tab,
245             p_location_stripe => FALSE,
249         --
246             p_raise_no_data   => FALSE
247         );
248         msg('Found '||NVL((p_supv_tab.LAST - p_supv_tab.FIRST)+1,0)||' records');
250         -- Delete all summary records for the supervisors and date ranges
251         -- we were given, since this is the data we're going to refresh
252         IF NVL(p_supv_tab.FIRST,0) > 0 THEN
253             msg('Deleting supervisor specific records and super-ordinate supervisors');
254             FOR i IN p_supv_tab.FIRST .. p_supv_tab.LAST LOOP
255                 --
256                 -- Get the details of all the supervisors we're going to delete
257                 l_loop := 0;
258                 FOR del_rec IN get_deletes_todo(
259                     p_supv_tab(i).supervisor_id,
260                     p_supv_tab(i).effective_start_date,
261                     p_supv_tab(i).effective_end_date
262                 ) LOOP
263                     l_loop := l_loop + 1;
264                     dbg(
265                         'Processing deletes for '||
266                         p_supv_tab(i).supervisor_id||' between '||
267                         p_supv_tab(i).effective_start_date||' and '||
268                         p_supv_tab(i).effective_end_date
269                     );
270                     --
271                     -- First subordinate is the current supervisor
272                     l_sub_id := del_rec.supervisor_id;
273                     --
274                     -- Get all the superordinates of the supervisor we're going to delete
275                     FOR sup_rec IN get_supsup(
276                         del_rec.supervisor_id,
277                         del_rec.effective_date
278                     ) LOOP
279                         dbg(
280                             'Removing '||del_rec.voluntary_char||'/'||del_rec.voluntary_char||' '||
281                             'values from supervisor '||sup_rec.sup_person_id||' subordinate '||
282                             l_sub_id
283                         );
284                         --
285                         UPDATE  hr_ptl_summary_data
286                         SET     sum_information4 = TO_NUMBER(sum_information4) - TO_NUMBER(del_rec.voluntary_char),
287                                 sum_information5 = TO_NUMBER(sum_information5) - TO_NUMBER(del_rec.involuntary_char)
288                         WHERE   sum_information2 = TO_CHAR(sup_rec.sup_person_id)
289                         AND     sum_information3 = TO_CHAR(l_sub_id)
290                         AND     sum_information1 = fnd_date.date_to_canonical(del_rec.effective_date)
291                         AND     sum_information_category = information_category;
292                         --
293                         -- Next subordinate is this supervisor 'cos we're going to step up the heirarchy
294                         l_sub_id := sup_rec.sup_person_id;
295                     END LOOP;
296                     --
297                     IF l_sub_id = del_rec.supervisor_id THEN
298                         dbg(
299                             'No rows returned by get_supsup for '||
300                             del_rec.supervisor_id||' and '||
301                             fnd_date.date_to_canonical(del_rec.effective_date)
302                         );
303                     END IF;
304                     --
305                 END LOOP;
306                 --
307                 IF l_loop = 0 THEN
308                     dbg('No rows returned by get_deletes_todo for '||
309                         p_supv_tab(i).supervisor_id||' '||
310                         fnd_date.date_to_canonical(p_supv_tab(i).effective_start_date)||' '||
311                         fnd_date.date_to_canonical(p_supv_tab(i).effective_end_date)||
312                         ' (data not previously record in summary, not an error)'
313                     );
314                 END IF;
315                 --
316                 -- Delete the supervisors we're going to refresh, we've just taken the
317                 -- values we're going to delete off of their superordinates
318                 DELETE
319                     FROM    hr_ptl_summary_data
320                     WHERE   effective_date BETWEEN
321                                 p_supv_tab(i).effective_start_date AND
322                                 p_supv_tab(i).effective_end_date
323                     AND     summary_context_id = p_supv_tab(i).supervisor_id
324                     AND     sum_information_category = information_category;
325                 --
326                 msg(
327                     'Supervisor '||
328                     p_supv_tab(i).supervisor_id||' '||
329                     p_supv_tab(i).effective_start_date||' -> '||
330                     p_supv_tab(i).effective_end_date||
331                     ' deleted '||SQL%ROWCOUNT||' rows'
332                 );
333             END LOOP;
334         END IF;
335         --
336     END build_delta_refresh_table;
337     --
338     -- ***********************************************************************
342     -- ***********************************************************************
339     -- * Do the actual insert into the summary table, used by the direct     *
340     -- * insert procedure and the cache flusher                              *
341     -- * TODO: Convert to bulk binds to improve performance?                 *
343     PROCEDURE do_insert(
344         p_eff_dt        IN DATE,
345         p_supv_id       IN NUMBER,
346         p_sub_supv_id   IN NUMBER,
347         p_vol_sep       IN NUMBER,
348         p_invol_sep     IN NUMBER
349     ) IS
350     BEGIN
351         dbg(
352             'Inserting new row for '||p_supv_id||'/'||p_sub_supv_id||'/'||p_eff_dt||
353             ' data '||p_vol_sep||'/'||p_invol_sep
354         );
355         INSERT INTO hr_ptl_summary_data (
356             summary_data_id,
357             summary_context_type,
358             summary_context_id,
359             effective_date,
360             created_by,
361             creation_date,
362             object_version_number,
363             last_updated_by,
364             last_update_date,
365             last_update_login,
366             request_id,
367             program_application_id,
368             program_id,
369             program_update_date,
370             sum_information_category,
371             sum_information1,
372             sum_information2,
373             sum_information3,
374             sum_information4,
375             sum_information5
376         ) VALUES (
377             hr_ptl_summary_data_s.NEXTVAL,
378             context_type,
379             p_supv_id,
380             p_eff_dt,
381             g_who_id,
382             g_who_date,
383             g_who_version,
384             g_who_id,
385             g_who_date,
386             g_who_login,
387             g_who_request,
388             g_who_application,
389             g_who_program,
390             g_who_date,
391             information_category,
392             fnd_date.date_to_canonical(p_eff_dt),
393             TO_CHAR(p_supv_id),
394             TO_CHAR(p_sub_supv_id),
395             TO_CHAR(p_vol_sep),
396             TO_CHAR(p_invol_sep)
397         );
398     END do_insert;
399     --
400     -- ***********************************************************************
401     -- * Insert data into a cache table, from where we'll insert into the    *
402     -- * portal summary table later. This saves us having to select back out *
403     -- * from the summary table                                              *
404     -- ***********************************************************************
405     PROCEDURE insert_cache_data(
406         p_supv_id       IN NUMBER,
407         p_sub_supv_id   IN NUMBER,
408         p_eff_dt        IN DATE,
409         p_vol_sep       IN NUMBER,
410         p_invol_sep     IN NUMBER
411     ) IS
412         --
413         -- Convert the date to a number to enable use to use it
414         -- as a hash key into a PL/SQL table
415         l_dt_num     NUMBER := TO_NUMBER(TO_CHAR(p_eff_dt,'YYYYMMDD'));
416         --
417         l_vol_sep    NUMBER;
418         l_invol_sep  NUMBER;
419     BEGIN
420         --
421         -- Make sure we've got a cache record for the effective date
422         IF NOT g_insert_cache.EXISTS(l_dt_num) THEN
423             g_insert_cache(l_dt_num).effective_date := p_eff_dt;
424         END IF;
425         --
426         -- Make sure we've got a cache record for the supervisor on the effective date
427         IF NOT g_insert_cache(l_dt_num).supervisor_rows.EXISTS(p_supv_id) THEN
428             g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).supervisor_id := p_supv_id;
429         END IF;
430         --
431         -- Make sure we've got a subordinate record cached for the required supervisor and date
432         IF NOT g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows.EXISTS(p_sub_supv_id) THEN
433             g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).subordinate_id   := p_sub_supv_id;
434             g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).voluntary_seps   := 0;
435             g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).involuntary_seps := 0;
436         END IF;
437         --
438         -- Get the current values against the cached record (neater syntax than doing the updates in one line)
439         l_vol_sep   := g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).voluntary_seps;
440         l_invol_sep := g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).involuntary_seps;
441         --
442         -- Add the passed values to the cached record
443         g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).voluntary_seps   := l_vol_sep + p_vol_sep;
444         g_insert_cache(l_dt_num).supervisor_rows(p_supv_id).subordinate_rows(p_sub_supv_id).involuntary_seps := l_invol_sep + p_invol_sep;
445         --
446     END insert_cache_data;
447     --
448     -- ***********************************************************************
449     -- * Flush the insert cache table to the database, then clear the cache  *
450     -- * in case the procedure gets run again in the same session            *
454         l_effdt     NUMBER;
451     -- ***********************************************************************
452     PROCEDURE flush_insert_cache IS
453         --
455         l_supv      NUMBER;
456         l_subor     NUMBER;
457     BEGIN
458         --
459         -- Only do this if we're not directly inserting into the summary table
460         IF NOT g_direct_insert THEN
461             --
462             -- Loop over all the effective dates for which we cached data
463             l_effdt := g_insert_cache.FIRST;
464             WHILE l_effdt IS NOT NULL LOOP
465                 --
466                 -- Loop over all the supervisors we cached for this date
467                 l_supv := g_insert_cache(l_effdt).supervisor_rows.FIRST;
468                 WHILE l_supv IS NOT NULL LOOP
469                     --
470                     -- Loop over all the subordinates cached for this supervisor on this date
471                     l_subor := g_insert_cache(l_effdt).supervisor_rows(l_supv).subordinate_rows.FIRST;
472                     WHILE l_subor IS NOT NULL LOOP
473                         --
474                         -- Do the actual insert
475                         do_insert(
476                             g_insert_cache(l_effdt).effective_date,
477                             g_insert_cache(l_effdt).supervisor_rows(l_supv).supervisor_id,
478                             g_insert_cache(l_effdt).supervisor_rows(l_supv).subordinate_rows(l_subor).subordinate_id,
479                             g_insert_cache(l_effdt).supervisor_rows(l_supv).subordinate_rows(l_subor).voluntary_seps,
480                             g_insert_cache(l_effdt).supervisor_rows(l_supv).subordinate_rows(l_subor).involuntary_seps
481                         );
482                         --
483                         -- Next subordinate
484                         l_subor := g_insert_cache(l_effdt).supervisor_rows(l_supv).subordinate_rows.NEXT(l_subor);
485                     END LOOP;
486                     --
487                     -- Next supervisor
488                     l_supv := g_insert_cache(l_effdt).supervisor_rows.NEXT(l_supv);
489                 END LOOP;
490                 --
491                 -- Next effective date
492                 l_effdt := g_insert_cache.NEXT(l_effdt);
493             END LOOP;
494             --
495             -- Bin the whole of the cache, in case the summary gets run twice in one session
496             g_insert_cache.DELETE;
497         END IF;
498     END flush_insert_cache;
499     --
500     -- ***********************************************************************
501     -- * Insert our specific summary data into the global summary table, and *
502     -- * fill in all the other necessary stuff too                           *
503     -- ***********************************************************************
504     PROCEDURE insert_summary_data(
505         p_supv_id       IN NUMBER,
506         p_sub_supv_id   IN NUMBER,
507         p_eff_dt        IN DATE,
508         p_vol_sep       IN NUMBER,
509         p_invol_sep     IN NUMBER
510     ) IS
511         --
512         -- Cursor to see if we've already inserted a row
513         -- for this date/supervisor/subordinate
514         CURSOR chk_exists(
515             cp_eff_dt   IN VARCHAR2,
516             cp_sup_id   IN VARCHAR2,
517             cp_sub_id   IN VARCHAR2
518         ) IS
519             -- Get rowid for fast updates and the current separation figures
520             SELECT      rowid,
521                         sum_information4,
522                         sum_information5
523             FROM        hr_ptl_summary_data
524             -- Make sure we're looking at the right rows
525             WHERE       sum_information_category = information_category
526             -- Use the text versions of the foreign keys to hit the index
527             AND         sum_information1 = cp_eff_dt
528             AND         sum_information2 = cp_sup_id
529             AND         sum_information3 = cp_sub_id;
530         --
531         l_rid           ROWID;
532         l_vol           hr_ptl_summary_data.sum_information4%TYPE;
533         l_invol         hr_ptl_summary_data.sum_information5%TYPE;
534         --
535     BEGIN
536         --
537         -- See if there's already a row for this supervisor/subordinate on this date
538         OPEN chk_exists(fnd_date.date_to_canonical(p_eff_dt),TO_CHAR(p_supv_id),TO_CHAR(p_sub_supv_id));
539         FETCH chk_exists INTO l_rid,l_vol,l_invol;
540         IF chk_exists%FOUND THEN
541             CLOSE chk_exists;
542             --
543             -- Update the existing row that we've just found
544             dbg(
545                 'Found row for '||p_supv_id||'/'||p_sub_supv_id||'/'||p_eff_dt||
546                 ' with data '||l_vol||'/'||l_invol||
547                 ' updating with '||p_vol_sep||'/'||p_invol_sep
548             );
549             --
550             -- TODO: Would it be quicker to just try updating the row and then do the insert
551             -- if nothing got updated (i.e. the row didn't exist)?
552             UPDATE hr_ptl_summary_data
553             SET    sum_information4 = TO_CHAR(TO_NUMBER(l_vol) + p_vol_sep),
554                    sum_information5 = TO_CHAR(TO_NUMBER(l_invol) + p_invol_sep)
555             WHERE  rowid = l_rid;
556             --
557         ELSE
558             CLOSE chk_exists;
559             --
560             -- Insert the data as an entirely new row
561             do_insert(p_eff_dt,p_supv_id,p_sub_supv_id,p_vol_sep,p_invol_sep);
562         END IF;
563         --
564     END insert_summary_data;
565     --
566     -- ***********************************************************************
567     -- * Either insert into the cache table for later flushing, or directly  *
568     -- * insert into the summary table. Cached version is quicker, but the   *
572     PROCEDURE proxy_insert_data(
569     -- * direct insert version will use less memory since the cached version *
570     -- * can result in quite a hefty PL/SQL table being created              *
571     -- ***********************************************************************
573         p_supv_id       IN NUMBER,
574         p_sub_supv_id   IN NUMBER,
575         p_eff_dt        IN DATE,
576         p_vol_sep       IN NUMBER,
577         p_invol_sep     IN NUMBER
578     ) IS
579     BEGIN
580         --
581         -- Insert directly into the table, a performance hit, since it first
582         -- has to select back from the table to see if the row's already there
583         IF g_direct_insert THEN
584             insert_summary_data(
585                 p_supv_id,
586                 p_sub_supv_id,
587                 p_eff_dt,
588                 p_vol_sep,
589                 p_invol_sep
590             );
591         --
592         -- Insert the data into the cache, must remember to flush it to the
593         -- database before the program exits
594         ELSE
595             insert_cache_data(
596                 p_supv_id,
597                 p_sub_supv_id,
598                 p_eff_dt,
599                 p_vol_sep,
600                 p_invol_sep
601             );
602         END IF;
603     END proxy_insert_data;
604     --
605     -- ***********************************************************************
606     -- * Calculate and insert the summarized data for each refresh record    *
607     -- * into the summary table                                              *
608     -- * Return a count of the records inserted                              *
609     -- ***********************************************************************
610     FUNCTION process_refresh_table(
611         p_supv_tab      IN OUT NOCOPY pay_events_wrapper.t_summary_refresh_tab_type
612     ) RETURN NUMBER IS
613         --
614         -- Main cursor to calculate the separations that have happened for a
615         -- supervisor between the given effective dates
616         CURSOR csr_get_supv(
617             cp_supv_id      IN NUMBER,
618             cp_st_dt        IN DATE,
619             cp_en_dt        IN DATE
620         ) IS
621             SELECT
622                 pos.actual_termination_date + 1        effective_date,
623                 SUM(DECODE(scr.separation_category_code,
624                              involuntary_code, 0,    -- Involuntary is zero
625                            DECODE(g_global_wmt,
626                                     'FTE', wmv.fte,
627                                     'HEAD', wmv.head,
628                                   0)))              voluntary_separations,
629                 SUM(DECODE(scr.separation_category_code,
630                              involuntary_code, DECODE(g_global_wmt,
631                                                         'FTE', wmv.fte,
632                                                         'HEAD', wmv.head,
633                                                       0),
634                            0))                      involuntary_separations
635             FROM
636                 per_all_assignments_f         asg
637               , per_periods_of_service        pos
638               , per_assignment_status_types   ast
639               , hri_cs_sepcr_v                scr
640               , hri_mb_wmv                    wmv
641             WHERE asg.assignment_id = wmv.assignment_id
642             AND asg.supervisor_id = cp_supv_id
643             AND asg.period_of_service_id = pos.period_of_service_id
644             AND ast.assignment_status_type_id = asg.assignment_status_type_id
645             AND NVL(pos.leaving_reason,'NA_EDW') = scr.separation_reason_code
646             AND pos.actual_termination_date <= TRUNC(SYSDATE)
647             AND asg.effective_end_date = pos.actual_termination_date
648             AND pos.actual_termination_date BETWEEN cp_st_dt
649                                                 AND cp_en_dt
650             AND pos.actual_termination_date BETWEEN wmv.effective_start_date
651                                                 AND wmv.effective_end_date
652             GROUP BY
653                 pos.actual_termination_date + 1;
654         --
655         l_dir_tot     NUMBER;
656         l_rup_tot     NUMBER;
657         l_prev_supv   NUMBER;
658         l_loop_cnt    NUMBER;
659         --
660     BEGIN
661         --
662         msg('Processing refresh table');
663         --
664         -- Check that there's data in the table
665         IF NVL(p_supv_tab.FIRST,0) < 1 THEN
666             msg('No data supplied in the refresh table');
667             RETURN 0;
668         END IF;
669         --
670         -- For each supervisor in the list, sum up their separations
671         l_dir_tot := 0;
672         l_rup_tot := 0;
673         dbg('Records range from '||p_supv_tab.FIRST||' to '||p_supv_tab.LAST);
674         FOR i IN p_supv_tab.FIRST .. p_supv_tab.LAST LOOP
675             l_loop_cnt := 0;
676             FOR l_supv_rec IN csr_get_supv(
677                 p_supv_tab(i).supervisor_id,
678                 p_supv_tab(i).effective_start_date,
679                 p_supv_tab(i).effective_end_date
680             ) LOOP
681                 l_loop_cnt := l_loop_cnt + 1;
682                 --
683                 -- Track back up the hierarchy, rolling the data up to the
684                 -- superordinate managers as we go
685                 dbg('Checking and adding super-ordinate managers for supervisor '||p_supv_tab(i).supervisor_id||' row '||i);
686                 l_prev_supv := -1;
687                 FOR rec IN get_supsup(
688                     p_supv_tab(i).supervisor_id,
689                     l_supv_rec.effective_date
690                 ) LOOP
694                     -- subordionate relative level should match the row number, i.e. we
691                     rec.row_number := get_supsup%ROWCOUNT;
692                     --
693                     -- Make sure we're traversing up the supervisor heirarchy properly, the
695                     -- should start with the superordinate who's one level up, then the
696                     -- manager that's a level up from that, and so on. This error should
697                     -- only ever occur if the supervisor heirarchy is corrupt, you should
698                     -- always have a chain of superordinate managers on sequential levels
699                     IF rec.row_number <> rec.sub_relative_level THEN
700                         dbg('ERROR: Supervisor heirarchy seems to be corrupt, sequential chain of superordinate managers is broken.');
701                         dbg('Subordinate manager:   '||p_supv_tab(i).supervisor_id);
702                         dbg('Effective date:        '||l_supv_rec.effective_date);
703                         dbg('Superordinate manager: '||rec.sup_person_id);
704                         dbg('Row number:            '||rec.row_number);
705                         dbg('Relative level       : '||rec.sub_relative_level);
706                     ELSE
707                         --
708                         -- Add a direct reports row for this superordinate on the current date
709                         dbg('Add direct reports row: '||rec.sup_person_id);
710                         proxy_insert_data(
711                             rec.sup_person_id,
712                             direct_report_id,
713                             l_supv_rec.effective_date,
714                             0,
715                             0
716                         );
717                         --
718                         -- The first superordinate has this manager as it's subordinate
719                         IF l_prev_supv = -1 THEN
720                             l_prev_supv := p_supv_tab(i).supervisor_id;
721                         END IF;
722                         --
723                         -- Add a row for the current superordinate manager and the
724                         -- subordinate of whom to which the current manager reports
725                         dbg('Add superordinate row: '||rec.sup_person_id||'/'||l_prev_supv);
726                         proxy_insert_data(
727                             rec.sup_person_id,
728                             l_prev_supv,
729                             l_supv_rec.effective_date,
730                             l_supv_rec.voluntary_separations,
731                             l_supv_rec.involuntary_separations
732                         );
733                         l_rup_tot := l_rup_tot + 1;
734                         --
735                         -- Subsequent superordinates have the previous manager as their subordinates
736                         l_prev_supv := rec.sup_person_id;
737                     END IF;
738                 END LOOP;
739                 --
740                 IF l_prev_supv = -1 THEN
741                     dbg(
742                         'No rows returned by get_supsup cursor for '||
743                         p_supv_tab(i).supervisor_id||
744                         ' and '||
745                         fnd_date.date_to_canonical(l_supv_rec.effective_date)
746                     );
747                 END IF;
748                 --
749                 -- Write some debugging info and insert the data
750                 dbg('Adding direct reports summary row for '||p_supv_tab(i).supervisor_id);
751                 proxy_insert_data(
752                     p_supv_tab(i).supervisor_id,
753                     direct_report_id,
754                     l_supv_rec.effective_date,
755                     l_supv_rec.voluntary_separations,
756                     l_supv_rec.involuntary_separations
757                 );
758                 l_dir_tot := l_dir_tot + 1;
759             END LOOP;
760             --
761             IF l_loop_cnt = 0 THEN
762                 dbg('No rows returned by csr_get_supv cursor for '||
763                     p_supv_tab(i).supervisor_id||', '||
764                     fnd_date.date_to_canonical(p_supv_tab(i).effective_start_date)||', '||
765                     fnd_date.date_to_canonical(p_supv_tab(i).effective_end_date)
766                 );
767             END IF;
768         END LOOP;
769         --
770         msg('Inserted '||l_dir_tot||' direct report rows');
771         msg('Inserted '||l_rup_tot||' rollup rows');
772         --
773         -- Flush the cache (this procedure won't do anything if we're doing direct inserts)
774         flush_insert_cache;
775         --
776         RETURN l_dir_tot + l_rup_tot;
777     END process_refresh_table;
778     --
779     -- ***********************************************************************
780     -- * Fully refresh all summary data for the Annualized Turnover portlets *
781     -- * within the specified time period                                    *
782     -- ***********************************************************************
783     PROCEDURE full_refresh(
784         errbuf          OUT NOCOPY VARCHAR2,
785         retcode         OUT NOCOPY NUMBER,
786         p_start_date    IN  VARCHAR2,
787         p_end_date      IN  VARCHAR2 DEFAULT eot_char
788     ) IS
789         --
790         l_start_date    DATE := fnd_date.canonical_to_date(p_start_date);
791         l_end_date      DATE := fnd_date.canonical_to_date(NVL(p_end_date,eot_char));
792         l_tot_rec       NUMBER := 0;
793         l_supv_tab      pay_events_wrapper.t_summary_refresh_tab_type;
794         --
795     BEGIN
796         -- Do the BIS refresh framework setup
797         IF bis_collection_utilities.setup(p_object_name => object_name) = FALSE THEN
798             dbg('Failed to setup bis collection utilities');
802         msg(g_start_full_msg);
799             errbuf := g_setup_failure;
800             raise_application_error(g_appl_err,g_setup_failure);
801         END IF;
803         dbg('Starting full refresh: '||l_start_date||'->'||l_end_date);
804         --
805         -- Get the list of all supervisors for which separations have occurred
806         -- within the *effective* dates specified by the input parameters
807         -- Any deletions from the summary table take place here
808         build_full_refresh_table(l_supv_tab,l_start_date,l_end_date);
809         dbg('Built refresh table: '||NVL(l_supv_tab.LAST,0)||' rows');
810         --
811         -- Process all the records in the refresh table, creates direct reports rows
812         -- and rolls back up the heirarchy as it goes
813         l_tot_rec := process_refresh_table(l_supv_tab);
814         dbg('Processed refresh table: '||l_tot_rec||' records');
815         --
816         -- Do the proper refresh framework wrapup
817         msg(g_success_message);
818         bis_collection_utilities.wrapup(
819             p_status        => TRUE,
820             p_count         => l_tot_rec,
821             p_message       => g_success_message,
822             p_period_from   => l_start_date,
823             p_period_to     => l_end_date
824         );
825         dbg('Run done OK');
826     --
827     -- Handle an exception by logging it with the collection framework
828     EXCEPTION WHEN OTHERS THEN
829         ROLLBACK;
830         dbg('Run failed, logging errors');
831         msg(g_failure_message||SQLERRM);
832         errbuf := g_failure_message||SQLERRM;
833         bis_collection_utilities.wrapup(
834             p_status        => FALSE,
835             p_count         => l_tot_rec,
836             p_message       => g_failure_message||SQLERRM,
837             p_period_from   => l_start_date,
838             p_period_to     => l_end_date
839         );
840         raise_application_error(g_appl_err,g_failure_message||SQLERRM);
841         --
842     END full_refresh;
843     --
844     -- ***********************************************************************
845     -- * Refresh the summary data for the Annualized Turnover portlets based *
846     -- * on the events that have occurred since we last ran this refresh     *
847     -- ***********************************************************************
848     PROCEDURE refresh_from_deltas(
849         errbuf          OUT NOCOPY VARCHAR2,
850         retcode         OUT NOCOPY NUMBER
851     ) IS
852         --
856         l_bis_end_date      DATE;
853         l_start_date        DATE;
854         l_end_date          DATE;
855         l_bis_start_date    DATE;
857         l_period_from       DATE;
858         l_period_to         DATE;
859         l_tot_rec           NUMBER := 0;
860         l_supv_tab          pay_events_wrapper.t_summary_refresh_tab_type;
861         --
862     BEGIN
863         -- Do the BIS refresh framework setup
864         IF bis_collection_utilities.setup(p_object_name => object_name) = FALSE THEN
865             dbg('Failed to set up bis collection utilities');
866             errbuf := g_setup_failure;
867             raise_application_error(g_appl_err,g_setup_failure);
868         END IF;
869         msg(g_start_delta_msg);
870         --
871         -- Get the dates of the last refresh of this program
872         bis_collection_utilities.get_last_refresh_dates(
873             object_name,
874             l_bis_start_date,
875             l_bis_end_date,
876             l_period_from,
877             l_period_to
878         );
879         --
880         -- The start of this refresh should be the time at which the last one started running so
881         -- that any changes made during the last run are picked up by this one
882         -- The end should be now
883         l_start_date := l_bis_start_date;
884         l_end_date   := SYSDATE;
885         --
886         dbg(
887             'Refreshing from deltas: '||
888             fnd_date.date_to_canonical(l_start_date)||
889             '->'||
890             fnd_date.date_to_canonical(l_end_date)
891         );
892         IF l_start_date > l_end_date THEN
893             dbg('ERROR: BIS collection utilities reports last refresh period later than current date, trying to continue anyway');
894         END IF;
895         --
896         -- Get the list of all supervisors for which separations have potentially
897         -- occurred within the *real* dates specified by the input parameters
898         -- Should use the payroll event model wrapper
899         -- Any deletions from the summary table take place here
900         build_delta_refresh_table(l_supv_tab,l_start_date,l_end_date);
901         dbg('Built delta refresh table: '||NVL(l_supv_tab.LAST,0)||' rows');
902         --
903         -- Process all the records in the refresh table, creates direct reports rows
904         -- and rolls back up the heirarchy as it goes
905         l_tot_rec := process_refresh_table(l_supv_tab);
906         dbg('Processed refresh table: '||l_tot_rec||' records');
907         --
908         -- Do the proper refresh framework wrapup
909         msg(g_success_message);
910         bis_collection_utilities.wrapup(
911             p_status        => TRUE,
912             p_count         => l_tot_rec,
913             p_message       => g_success_message,
914             p_period_from   => l_start_date,
915             p_period_to     => l_end_date
916         );
917         dbg('Run completed OK');
918     --
919     -- Handle an exception by logging it with the collection framework
920     EXCEPTION WHEN OTHERS THEN
921         ROLLBACK;
922         dbg('Run failed, logging errors');
923         msg(g_failure_message||SQLERRM);
924         errbuf := g_failure_message||SQLERRM;
925         bis_collection_utilities.wrapup(
926             p_status        => FALSE,
927             p_count         => l_tot_rec,
928             p_message       => g_failure_message||SQLERRM,
929             p_period_from   => l_start_date,
930             p_period_to     => l_end_date
931         );
932         raise_application_error(g_appl_err,g_failure_message||SQLERRM);
933         --
934     END refresh_from_deltas;
935     --
936     -- ***********************************************************************
937     -- * Special debug modes just set the globals (and the wrapper log mode) *
938     -- * and then call the normal routines                                   *
939     -- ***********************************************************************
940     PROCEDURE full_refresh_debug(
941         errbuf          OUT NOCOPY VARCHAR2,
942         retcode         OUT NOCOPY NUMBER,
943         p_start_date    IN  VARCHAR2,
944         p_end_date      IN  VARCHAR2 DEFAULT eot_char
945     ) IS
946     BEGIN
947         set_debugging(TRUE);
948         full_refresh(
949             errbuf       => errbuf,
950             retcode      => retcode,
951             p_start_date => p_start_date,
952             p_end_date   => p_end_date
953         );
954     END full_refresh_debug;
955     --
956     PROCEDURE refresh_from_deltas_debug(
957         errbuf          OUT NOCOPY VARCHAR2,
958         retcode         OUT NOCOPY NUMBER
959     ) IS
960     BEGIN
961         set_debugging(TRUE);
962         pay_events_wrapper.set_concurrent_logging(TRUE);
963         pay_events_wrapper.set_debugging(TRUE);
964         refresh_from_deltas(errbuf,retcode);
965     END refresh_from_deltas_debug;
966     --
967 BEGIN
968     -- Start up this package
969     initialise_globals;
970     --
971 END hri_dbi_wmv_separation;