DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_OPL_SUP_ABSNC

Source


1 PACKAGE BODY hri_opl_sup_absnc AS
2 /* $Header: hriouaba.pkb 120.7 2006/02/20 07:17:30 jtitmas noship $ */
3 
4   -- Simple table types
5   TYPE g_date_tab_type IS TABLE OF DATE INDEX BY BINARY_INTEGER;
6   TYPE g_number_tab_type IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
7   TYPE g_varchar2_tab_type IS TABLE OF VARCHAR2(30) INDEX BY BINARY_INTEGER;
8 
9   -- PL/SQL table representing database table
10   g_tab_sup_person_id         g_number_tab_type;
11   g_tab_effective_date        g_date_tab_type;
12   g_tab_abs_sk_fk             g_number_tab_type;
13   g_tab_sup_direct_ind        g_number_tab_type;
14   g_tab_abs_drtn_days         g_number_tab_type;
15   g_tab_abs_drtn_hrs          g_number_tab_type;
16   g_tab_abs_start_blnc        g_number_tab_type;
17   g_tab_abs_nstart_blnc       g_number_tab_type;
18   g_tab_abs_ntfctn_start      g_number_tab_type;
19   g_tab_abs_ntfctn_nstart     g_number_tab_type;
20   g_tab_abs_category_code     g_varchar2_tab_type;
21   g_tab_abs_reason_code       g_varchar2_tab_type;
22   g_tab_abs_person_id         g_number_tab_type;
23   g_tab_index                 PLS_INTEGER;
24 
25   -- End of time
26   g_end_of_time    DATE := hr_general.end_of_time;
27 
28   -- Global HRI Multithreading Array
29   g_mthd_action_array       HRI_ADM_MTHD_ACTIONS%rowtype;
30 
31   -- Global parameters
32   g_refresh_start_date      DATE;
33   g_full_refresh            VARCHAR2(30);
34 
35   g_sysdate                 DATE;
36   g_user                    NUMBER;
37 
38 -- ----------------------------------------------------------------------------
39 -- Runs given sql statement dynamically
40 -- ----------------------------------------------------------------------------
41 PROCEDURE run_sql_stmt_noerr(p_sql_stmt   VARCHAR2) IS
42 
43 BEGIN
44 
45   EXECUTE IMMEDIATE p_sql_stmt;
46 
47 EXCEPTION WHEN OTHERS THEN
48 
49   null;
50 
51 END run_sql_stmt_noerr;
52 
53 -- ----------------------------------------------------------------------------
54 -- Sets global parameters from multi-threading process parameters
55 -- ----------------------------------------------------------------------------
56 PROCEDURE set_parameters(p_mthd_action_id   IN NUMBER,
57                          p_mthd_stage_code  IN VARCHAR2) IS
58 
59   l_dbi_collection_start_date     DATE;
60 
61 BEGIN
62 
63 -- If parameters haven't already been set, then set them
64   IF (g_refresh_start_date IS NULL OR
65       p_mthd_stage_code = 'PRE_PROCESS') THEN
66 
67     l_dbi_collection_start_date :=
68            hri_oltp_conc_param.get_date_parameter_value
69             (p_parameter_name     => 'FULL_REFRESH_FROM_DATE',
70              p_process_table_name => 'HRI_MDP_SUP_ABSNC_OCC_CT');
71 
72     -- If called for the first time set the defaulted parameters
73     IF (p_mthd_stage_code = 'PRE_PROCESS') THEN
74 
75       g_full_refresh :=
76            hri_oltp_conc_param.get_parameter_value
77             (p_parameter_name     => 'FULL_REFRESH',
78              p_process_table_name => 'HRI_MDP_SUP_ABSNC_OCC_CT');
79 
80       -- Log defaulted parameters so the slave processes pick up
81       hri_opl_multi_thread.update_parameters
82        (p_mthd_action_id    => p_mthd_action_id,
83         p_full_refresh      => g_full_refresh,
84         p_global_start_date => l_dbi_collection_start_date);
85 
86     END IF;
87 
88     g_mthd_action_array    := hri_opl_multi_thread.get_mthd_action_array
89                                (p_mthd_action_id);
90     g_refresh_start_date   := g_mthd_action_array.collect_from_date;
91     g_full_refresh         := g_mthd_action_array.full_refresh_flag;
92     g_sysdate              := sysdate;
93     g_user                 := fnd_global.user_id;
94 
95     hri_bpl_conc_log.dbg('Full refresh:   ' || g_full_refresh);
96     hri_bpl_conc_log.dbg('Collect from:    N/A');
97   END IF;
98 
99 END set_parameters;
100 
101 -- ----------------------------------------------------------------------------
102 -- Inserts row into PL/SQL table for future bulk insert
103 -- ----------------------------------------------------------------------------
104 PROCEDURE insert_row
105  (p_sup_person_id         IN NUMBER,
106   p_effective_date        IN DATE,
107   p_abs_sk_fk             IN NUMBER,
108   p_sup_direct_ind        IN NUMBER,
109   p_abs_drtn_days         IN NUMBER,
110   p_abs_drtn_hrs          IN NUMBER,
111   p_abs_start_blnc        IN NUMBER,
112   p_abs_nstart_blnc       IN NUMBER,
113   p_abs_ntfctn_start      IN NUMBER,
114   p_abs_ntfctn_nstart     IN NUMBER,
115   p_abs_category_code     IN VARCHAR2,
116   p_abs_reason_code       IN VARCHAR2,
117   p_abs_person_id         IN NUMBER) IS
118 
119 BEGIN
120 
121   g_tab_index := g_tab_index + 1;
122   g_tab_sup_person_id(g_tab_index) := p_sup_person_id;
123   g_tab_effective_date(g_tab_index) := p_effective_date;
124   g_tab_abs_sk_fk(g_tab_index) := p_abs_sk_fk;
125   g_tab_sup_direct_ind(g_tab_index) := p_sup_direct_ind;
126   g_tab_abs_drtn_days(g_tab_index) := p_abs_drtn_days;
127   g_tab_abs_drtn_hrs(g_tab_index) := p_abs_drtn_hrs;
128   g_tab_abs_start_blnc(g_tab_index) := p_abs_start_blnc;
129   g_tab_abs_nstart_blnc(g_tab_index) := p_abs_nstart_blnc;
130   g_tab_abs_ntfctn_start(g_tab_index) := p_abs_ntfctn_start;
131   g_tab_abs_ntfctn_nstart(g_tab_index) := p_abs_ntfctn_nstart;
132   g_tab_abs_category_code(g_tab_index) := p_abs_category_code;
133   g_tab_abs_reason_code(g_tab_index) := p_abs_reason_code;
134   g_tab_abs_person_id(g_tab_index) := p_abs_person_id;
135 
136 END insert_row;
137 
138 -- ----------------------------------------------------------------------------
139 -- Empties PL/SQL table into database table and commits
140 -- ----------------------------------------------------------------------------
141 PROCEDURE bulk_insert_rows IS
142 
143 BEGIN
144 
145   g_user := fnd_global.user_id;
146   g_sysdate := sysdate;
147 
148   -- Bulk insert rows if any exist
149   IF (g_tab_index > 0) THEN
150 
151     FORALL i IN 1..g_tab_index
152       INSERT INTO hri_mdp_sup_absnc_occ_ct
153        (supervisor_person_id
154        ,effective_date
155        ,absence_sk_fk
156        ,direct_ind
157        ,abs_drtn_days
158        ,abs_drtn_hrs
159        ,abs_start_blnc
160        ,abs_nstart_blnc
161        ,abs_ntfctn_days_start_blnc
162        ,abs_ntfctn_days_nstart_blnc
163        ,absence_category_code
164        ,absence_reason_code
165        ,abs_person_id
166        ,last_update_date
167        ,last_updated_by
168        ,last_update_login
169        ,created_by
170        ,creation_date)
171        VALUES
172         (g_tab_sup_person_id(i),
173          g_tab_effective_date(i),
174          g_tab_abs_sk_fk(i),
175          g_tab_sup_direct_ind(i),
176          g_tab_abs_drtn_days(i),
177          g_tab_abs_drtn_hrs(i),
178          g_tab_abs_start_blnc(i),
179          g_tab_abs_nstart_blnc(i),
180          g_tab_abs_ntfctn_start(i),
181          g_tab_abs_ntfctn_nstart(i),
182          g_tab_abs_category_code(i),
183          g_tab_abs_reason_code(i),
184          g_tab_abs_person_id(i),
185          g_sysdate,
186          g_user,
187          g_user,
188          g_user,
189          g_sysdate);
190 
191     -- commit
192     commit;
193 
194   END IF;
195 
196   g_tab_index := 0;
197 
198 END bulk_insert_rows;
199 
200 -- ----------------------------------------------------------------------------
201 -- Caches the supervisor chain for a person at a point in time
202 -- ----------------------------------------------------------------------------
203 PROCEDURE load_supervisor_chain
204    (p_person_id       IN NUMBER,
205     p_effective_date  IN DATE,
206     p_supervisor_tab  OUT NOCOPY g_number_tab_type,
207     p_directs_tab     OUT NOCOPY g_number_tab_type,
208     p_valid_to_date   OUT NOCOPY DATE) IS
209 
210   CURSOR sup_chain_csr IS
211   SELECT
212    sup_person_id
213   ,sub_relative_level
214   ,DECODE(sub_relative_level, 1, 1, 0)  direct_ind
215   ,effective_end_date
216   FROM
217    hri_cs_suph
218   WHERE sub_person_id = p_person_id
219   AND p_effective_date BETWEEN effective_start_date
220                        AND effective_end_date;
221 
222   l_date_tab       g_date_tab_type;
223   l_empty_tab      g_number_tab_type;
224 
225 BEGIN
226 
227   -- Reset output variables
228   p_supervisor_tab := l_empty_tab;
229   p_directs_tab    := l_empty_tab;
230 
231   -- Loop through supervisor records
232   FOR sup_rec IN sup_chain_csr LOOP
233 
234     -- Keep track of the minimum valid to date
235     IF (p_valid_to_date IS NULL OR
236         sup_rec.effective_end_date < p_valid_to_date) THEN
237       p_valid_to_date := sup_rec.effective_end_date;
238     END IF;
239 
240     -- Add to chain record
241     IF (sup_rec.sub_relative_level > 0) THEN
242       p_supervisor_tab(sup_rec.sub_relative_level) := sup_rec.sup_person_id;
243       p_directs_tab(sup_rec.sub_relative_level) := sup_rec.direct_ind;
244     END IF;
245 
246   END LOOP;
247 
248 END load_supervisor_chain;
249 
250 -- -----------------------------------------------------------------------------
251 -- Processes either:
252 --    FULL REFRESH - All absences for a person within collection range
253 --    INCR REFRESH - All absences within given range of absence ids
254 --
255 -- The corresponding input parameters should be set, either
256 --    p_person_id - for full refresh
257 --  OR
258 --   p_start/end_abs_id - for incr refresh
259 --  NOT BOTH
260 --
261 -- Pushing of suph into absence day occurs in PL/SQL to reduce buffer reads
262 -- -----------------------------------------------------------------------------
263 PROCEDURE process_set(p_person_id     IN NUMBER,
264                       p_start_abs_id  IN NUMBER,
265                       p_end_abs_id    IN NUMBER) IS
266 
267   -- Absence details per person
268   CURSOR full_absence_csr IS
269   SELECT
270    abs_fct.effective_date
271   ,abs_fct.absence_sk_fk
272   ,abs_fct.abs_drtn_days
273   ,abs_fct.abs_drtn_hrs
274   ,abs_fct.abs_start_ind
275   ,abs_fct.abs_ntfctn_days_blnc
276   ,abs_dim.absence_category_code
277   ,abs_dim.absence_reason_code
278   ,abs_dim.abs_person_id
279   FROM
280    hri_mb_utl_absnc_ct  abs_fct
281   ,hri_cs_absence_ct    abs_dim
282   WHERE abs_dim.abs_person_id = p_person_id
283   AND abs_dim.absence_sk_pk = abs_fct.absence_sk_fk
284   ORDER BY abs_fct.effective_date;
285 
286   -- Absence details per range
287   CURSOR incr_absence_csr IS
288   SELECT
289    abs_fct.effective_date
290   ,abs_fct.absence_sk_fk
291   ,abs_fct.abs_drtn_days
292   ,abs_fct.abs_drtn_hrs
293   ,abs_fct.abs_start_ind
294   ,abs_fct.abs_ntfctn_days_blnc
295   ,abs_dim.absence_category_code
296   ,abs_dim.absence_reason_code
297   ,abs_dim.abs_person_id
298   FROM
299    hri_mb_utl_absnc_ct  abs_fct
300   ,hri_cs_absence_ct    abs_dim
301   ,hri_eq_sup_absnc     eq
302   WHERE abs_dim.absence_sk_pk = eq.source_id
303   AND eq.source_type = 'ABSENCE'
304   AND eq.source_id BETWEEN p_start_abs_id
305                    AND p_end_abs_id
306   AND abs_dim.absence_sk_pk = abs_fct.absence_sk_fk
307   ORDER BY abs_person_id, abs_fct.effective_date;
308 
309   -- PL/SQL table for cursor fetch
310   l_abs_effective_date      g_date_tab_type;
311   l_abs_sk_fk               g_number_tab_type;
312   l_abs_drtn_days           g_number_tab_type;
313   l_abs_drtn_hrs            g_number_tab_type;
314   l_abs_start_ind           g_number_tab_type;
315   l_abs_ntfctn_days_blnc    g_number_tab_type;
316   l_abs_category_code       g_varchar2_tab_type;
317   l_abs_reason_code         g_varchar2_tab_type;
318   l_abs_person_id           g_number_tab_type;
319 
320   -- New supervisor table
321   l_new_sup_ids             g_varchar2_tab_type;
322   l_empty_tab               g_varchar2_tab_type;
323 
324   -- Whether the absence is new for the supervisor
325   l_new_sup                 BOOLEAN;
326   l_sup_abs_start_ind       NUMBER;
327   l_last_abs_sk_fk          NUMBER;
328 
329   -- Supervisor chain
330   l_sup_ids                 g_number_tab_type;
331   l_sup_direct_ind          g_number_tab_type;
332   l_sup_valid_to            DATE;
333   l_sup_valid_for           NUMBER;
334 
335 BEGIN
336 
337   -- Split out full and incremental refresh
338   IF (p_person_id IS NOT NULL) THEN
339 
340     -- Fetch records from full refresh cursor
341     OPEN full_absence_csr;
342     FETCH full_absence_csr BULK COLLECT INTO
343       l_abs_effective_date,
344       l_abs_sk_fk,
345       l_abs_drtn_days,
346       l_abs_drtn_hrs,
347       l_abs_start_ind,
348       l_abs_ntfctn_days_blnc,
349       l_abs_category_code,
350       l_abs_reason_code,
351       l_abs_person_id;
352     CLOSE full_absence_csr;
353 
354   ELSE
355 
356     -- Fetch records from incremental refresh cursor
357     OPEN incr_absence_csr;
358     FETCH incr_absence_csr BULK COLLECT INTO
359       l_abs_effective_date,
360       l_abs_sk_fk,
361       l_abs_drtn_days,
362       l_abs_drtn_hrs,
363       l_abs_start_ind,
364       l_abs_ntfctn_days_blnc,
365       l_abs_category_code,
366       l_abs_reason_code,
367       l_abs_person_id;
368     CLOSE incr_absence_csr;
369 
370   END IF;
371 
372   -- If any absences found then process them
373   IF (l_abs_sk_fk.EXISTS(1)) THEN
374 
375     -- Initialize supervisor chain
376     load_supervisor_chain
377      (p_person_id      => l_abs_person_id(1),
378       p_effective_date => l_abs_effective_date(1),
379       p_supervisor_tab => l_sup_ids,
380       p_directs_tab    => l_sup_direct_ind,
381       p_valid_to_date  => l_sup_valid_to);
382     l_sup_valid_for := l_abs_person_id(1);
383 
384     -- Loop through absences
385     FOR i IN l_abs_sk_fk.FIRST..l_abs_sk_fk.LAST LOOP
386 
387       -- Reset supervisor cache if a new absence is encountered
388       -- Bug 5049096
389       IF (l_abs_sk_fk(i) <> l_last_abs_sk_fk) THEN
390         l_new_sup_ids := l_empty_tab;
391       END IF;
392 
393       -- Check if supervisor chain is still valid
394       IF (l_sup_valid_to < l_abs_effective_date(i) OR
395           l_sup_valid_for <> l_abs_person_id(i)) THEN
396         load_supervisor_chain
397          (p_person_id      => l_abs_person_id(i),
398           p_effective_date => l_abs_effective_date(i),
399           p_supervisor_tab => l_sup_ids,
400           p_directs_tab    => l_sup_direct_ind,
401           p_valid_to_date  => l_sup_valid_to);
402         l_sup_valid_for := l_abs_person_id(i);
403       END IF;
404 
405       -- Check supervisor chain exists
406       IF (l_sup_ids.EXISTS(1)) THEN
407 
408         -- Insert absence details for each supervisor
409         FOR j IN l_sup_ids.FIRST..l_sup_ids.LAST LOOP
410 
411           -- Determine whether the supervisor encountered is new
412           -- for this absence occurrence
413           IF (l_new_sup_ids.EXISTS(l_sup_ids(j))) THEN
414             l_new_sup := FALSE;
415           ELSE
416             l_new_sup := TRUE;
417             l_new_sup_ids(l_sup_ids(j)) := 'Y';
418           END IF;
419 
420           -- Bug 4889166
421           -- Determine whether to set absence start or nstart values
422           -- The absence start balances should be set for the first day
423           -- of the absence (derived from the fact indicator) or
424           -- if there has been a supervisor change and it is the first
425           -- day of the absence for a new supervisor
426           IF (l_abs_start_ind(i) = 1 OR l_new_sup) THEN
427             l_sup_abs_start_ind := 1;
428           ELSE
429             l_sup_abs_start_ind := 0;
430           END IF;
431 
432           -- Call procedure to insert row
433           insert_row
434            (p_sup_person_id     => l_sup_ids(j),
435             p_effective_date    => l_abs_effective_date(i),
436             p_abs_sk_fk         => l_abs_sk_fk(i),
437             p_sup_direct_ind    => l_sup_direct_ind(j),
438             p_abs_drtn_days     => l_abs_drtn_days(i),
439             p_abs_drtn_hrs      => l_abs_drtn_hrs(i),
440             p_abs_start_blnc    => l_sup_abs_start_ind,
441             p_abs_nstart_blnc   => 1 - l_sup_abs_start_ind,
442             p_abs_ntfctn_start  => l_abs_ntfctn_days_blnc(i) * l_sup_abs_start_ind,
443             p_abs_ntfctn_nstart => l_abs_ntfctn_days_blnc(i) * (1 - l_sup_abs_start_ind),
444             p_abs_category_code => l_abs_category_code(i),
445             p_abs_reason_code   => l_abs_reason_code(i),
446             p_abs_person_id     => l_abs_person_id(i));
447         END LOOP;
448 
449       END IF; -- supervisors exist
450 
451       -- Store absence key
452       l_last_abs_sk_fk := l_abs_sk_fk(i);
453 
454     END LOOP; -- absences
455 
456   END IF; -- absences exist
457 
458   -- Bulk insert rows if limit is reached
459   IF (g_tab_index > 2000) THEN
460     bulk_insert_rows;
461   END IF;
462 
463 END process_set;
464 
465 -- Truncates and repopulates the supervisor events helper table
466 PROCEDURE process_range_full(p_start_psn_id    IN NUMBER,
467                              p_end_psn_id      IN NUMBER) IS
468 
469   -- Person in range
470   CURSOR person_csr IS
471   SELECT DISTINCT
472    abs_person_id
473   FROM hri_cs_absence_ct
474   WHERE abs_person_id BETWEEN p_start_psn_id AND p_end_psn_id;
475 
476 BEGIN
477 
478   -- Reset count
479   g_tab_index := 0;
480 
481   -- Loop through people
482   FOR person_rec IN person_csr LOOP
483 
484     -- Process people one at a time
485     process_set
486      (p_person_id    => person_rec.abs_person_id,
487       p_start_abs_id => to_number(null),
488       p_end_abs_id   => to_number(null));
489 
490   END LOOP;
491 
492   -- Insert any remaining rows for range
493   bulk_insert_rows;
494 
495 END process_range_full;
496 
497 -- -----------------------------------------------------------------------------
498 -- Processes incremental range
499 -- -----------------------------------------------------------------------------
500 PROCEDURE process_range_incr(p_start_abs_id    IN NUMBER,
501                              p_end_abs_id      IN NUMBER) IS
502 
503 BEGIN
504 
505   -- Delete changed rows
506   DELETE FROM hri_mdp_sup_absnc_occ_ct tab
507   WHERE tab.absence_sk_fk IN
508    (SELECT eq.source_id
509     FROM hri_eq_sup_absnc  eq
510     WHERE eq.source_id BETWEEN p_start_abs_id AND p_end_abs_id
511     AND eq.source_type = 'ABSENCE');
512 
513   -- Reset PL/SQL tables
514   g_tab_index := 0;
515 
516   -- Process set of absences in range
517   process_set
518    (p_person_id    => to_number(null),
519     p_start_abs_id => p_start_abs_id,
520     p_end_abs_id   => p_end_abs_id);
521 
522   -- Insert rows
523   bulk_insert_rows;
524 
525 END process_range_incr;
526 
527 -- ----------------------------------------------------------------------------
528 -- PROCESS_RANGE
529 -- This procedure includes the logic required for processing the assignments
530 -- which have been included in the range. It is dynamically invoked by the
531 -- multithreading child process. It manages the multithreading ranges.
532 -- ----------------------------------------------------------------------------
533 PROCEDURE process_range(errbuf             OUT NOCOPY VARCHAR2
534                        ,retcode            OUT NOCOPY NUMBER
535                        ,p_mthd_action_id   IN NUMBER
536                        ,p_mthd_range_id    IN NUMBER
537                        ,p_start_object_id  IN NUMBER
538                        ,p_end_object_id    IN NUMBER) IS
539 
540 BEGIN
541 
542 -- Set the parameters
543   set_parameters
544    (p_mthd_action_id  => p_mthd_action_id,
545     p_mthd_stage_code => 'PROCESS_RANGE');
546 
547 -- Process range in corresponding refresh mode
548   IF g_full_refresh = 'Y' THEN
549     process_range_full
550      (p_start_psn_id => p_start_object_id,
551       p_end_psn_id   => p_end_object_id);
552   ELSE
553     process_range_incr
554      (p_start_abs_id => p_start_object_id,
555       p_end_abs_id   => p_end_object_id);
556   END IF;
557 
558 END process_range;
559 
560 -- ----------------------------------------------------------------------------
561 -- Translates people whose supervisor chains have changed into absences
562 -- ----------------------------------------------------------------------------
563 PROCEDURE find_absences_for_supervisors IS
564 
565 BEGIN
566 
567   -- Insert absences affected by supervisor changes
568   INSERT INTO hri_eq_sup_absnc
569    (source_id
570    ,source_type)
571   SELECT
572    dim.absence_sk_pk  source_id
573   ,'ABSENCE'          source_type
574   FROM
575    hri_cs_absence_ct  dim
576   ,hri_eq_sup_absnc   eq
577   WHERE eq.source_type = 'SUPERVISOR'
578   AND eq.source_id = dim.abs_person_id
579   AND dim.abs_end_date >= eq.erlst_evnt_effective_date
580   AND NOT EXISTS
581    (SELECT null
582     FROM hri_eq_sup_absnc eq_abs
583     WHERE eq_abs.source_id = dim.absence_sk_pk
584     AND eq_abs.source_type = 'ABSENCE');
585 
586   commit;
587 
588 END find_absences_for_supervisors;
589 
590 -- ----------------------------------------------------------------------------
591 -- Pre process entry point
592 -- ----------------------------------------------------------------------------
593 PROCEDURE pre_process(p_mthd_action_id  IN NUMBER,
594                       p_sqlstr          OUT NOCOPY VARCHAR2) IS
595 
596   l_sql_stmt      VARCHAR2(2000);
597   l_dummy1        VARCHAR2(2000);
598   l_dummy2        VARCHAR2(2000);
599   l_schema        VARCHAR2(400);
600 
601 BEGIN
602 
603   -- Set parameter globals
604   set_parameters
605    (p_mthd_action_id  => p_mthd_action_id,
606     p_mthd_stage_code => 'PRE_PROCESS');
607 
608   -- Get HRI schema name - get_app_info populates l_schema
609   IF fnd_installation.get_app_info('HRI',l_dummy1, l_dummy2, l_schema) THEN
610     null;
611   END IF;
612 
613   -- Disable WHO trigger
614   run_sql_stmt_noerr('ALTER TRIGGER HRI_MDP_SUP_ABSNC_OCC_CT_WHO DISABLE');
615 
616   -- ********************
617   -- Full Refresh Section
618   -- ********************
619   IF (g_full_refresh = 'Y' OR
620       g_mthd_action_array.foundation_hr_flag = 'Y') THEN
621 
622     -- Empty out absence dimension table
623     l_sql_stmt := 'TRUNCATE TABLE ' || l_schema || '.HRI_MDP_SUP_ABSNC_OCC_CT';
624     EXECUTE IMMEDIATE(l_sql_stmt);
625 
626     -- In shared HR mode do not return a SQL statement so that the
627     -- process_range and post_process will not be executed
628     IF (g_mthd_action_array.foundation_hr_flag = 'Y') THEN
629 
630       -- Call post processing API
631       post_process
632        (p_mthd_action_id => p_mthd_action_id);
633 
634     ELSE
635 
636       -- Drop all the indexes on the table
637       hri_utl_ddl.log_and_drop_indexes
638        (p_application_short_name => 'HRI',
639         p_table_name             => 'HRI_MDP_SUP_ABSNC_OCC_CT',
640         p_table_owner            => l_schema);
641 
642       -- Set the SQL statement for the entire range
643       p_sqlstr :=
644         'SELECT /*+ PARALLEL(asg, DEFAULT, DEFAULT) */ DISTINCT
645            abs_person_id object_id
646          FROM hri_cs_absence_ct
647          ORDER BY abs_person_id';
648 
649     END IF;
650 
651   ELSE
652 
653     -- Process the event queue
654     find_absences_for_supervisors;
655 
656     -- Set the SQL statement for the incremental range
657       p_sqlstr :=
658         'SELECT
659            source_id object_id
660          FROM hri_eq_sup_absnc
661          WHERE source_type = ''ABSENCE''
662          ORDER BY source_id';
663 
664   END IF;
665 
666 END pre_process;
667 
668 -- ----------------------------------------------------------------------------
669 -- Post process entry point
670 -- ----------------------------------------------------------------------------
671 PROCEDURE post_process(p_mthd_action_id NUMBER) IS
672 
673   l_sql_stmt      VARCHAR2(2000);
674   l_dummy1        VARCHAR2(2000);
675   l_dummy2        VARCHAR2(2000);
676   l_schema        VARCHAR2(400);
677 
678 BEGIN
679 
680   -- Check parameters are set
681   set_parameters
682    (p_mthd_action_id  => p_mthd_action_id,
683     p_mthd_stage_code => 'POST_PROCESS');
684 
685   IF (p_mthd_action_id > -1) THEN
686 
687     -- Log process end
688     hri_bpl_conc_log.record_process_start('HRI_MDP_SUP_ABSNC_OCC_CT');
689     hri_bpl_conc_log.log_process_end(
690        p_status         => TRUE
691       ,p_period_from    => TRUNC(g_refresh_start_date)
692       ,p_period_to      => TRUNC(SYSDATE)
693       ,p_attribute1     => g_full_refresh);
694 
695   END IF;
696 
697   -- Enable WHO trigger
698   run_sql_stmt_noerr('ALTER TRIGGER HRI_MDP_SUP_ABSNC_OCC_CT_WHO ENABLE');
699 
700   -- Get HRI schema name - get_app_info populates l_schema
701   IF fnd_installation.get_app_info('HRI',l_dummy1, l_dummy2, l_schema) THEN
702     null;
703   END IF;
704 
705   -- Recreate indexes
706   IF (g_full_refresh = 'Y') THEN
707     hri_utl_ddl.recreate_indexes
708      (p_application_short_name => 'HRI',
709       p_table_name             => 'HRI_MDP_SUP_ABSNC_OCC_CT',
710       p_table_owner            => l_schema);
711   END IF;
712 
713   -- Empty out absence summary event queue
714   l_sql_stmt := 'TRUNCATE TABLE ' || l_schema || '.HRI_EQ_SUP_ABSNC';
715   EXECUTE IMMEDIATE(l_sql_stmt);
716 
717 END post_process;
718 
719 -- Populates table in a single thread
720 PROCEDURE single_thread_process(p_full_refresh_flag  IN VARCHAR2) IS
721 
722   l_end_abs_id  NUMBER;
723   l_end_psn_id  NUMBER;
724   l_dummy       VARCHAR2(32000);
725   l_from_date   DATE := hri_bpl_parameter.get_bis_global_start_date;
726 
727 BEGIN
728 
729 -- get max assignment id
730   SELECT max(person_id) INTO l_end_psn_id
731   FROM per_all_people_f;
732   SELECT max(absence_attendance_id) INTO l_end_abs_id
733   FROM per_absence_attendances;
734 
735 -- Set globals
736   g_full_refresh              := p_full_refresh_flag;
737   g_refresh_start_date        := l_from_date;
738   g_end_of_time               := hr_general.end_of_time;
739   l_dummy := 'HRI';
740 
741 -- Truncate table
742   EXECUTE IMMEDIATE 'TRUNCATE TABLE ' || l_dummy || '.hri_mdp_sup_absnc_occ_ct';
743 
744 -- Process range
745   IF (p_full_refresh_flag = 'Y') THEN
746     process_range_full(0, l_end_psn_id);
747   ELSE
748     process_range_incr(0, l_end_abs_id);
749   END IF;
750 
751 -- Truncate table
752   EXECUTE IMMEDIATE 'TRUNCATE TABLE ' || l_dummy || '.hri_eq_sup_absnc';
753 
754 END single_thread_process;
755 
756 END hri_opl_sup_absnc;