DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_OPL_PER_ORGCC

Source


1 PACKAGE BODY HRI_OPL_PER_ORGCC AS
2 /* $Header: hrippcc.pkb 120.0 2005/05/29 06:56:42 appldev noship $ */
3 --
4 -- Types required to support tables of column values.
5 --
6 -- @@ Code specific to this view/table below
7 -- @@ INTRUCTION TO DEVELOPER:
8 -- @@ 1/ For each column in your 'source view' create a TYPE in the format
9 -- @@    g_<col_name>_type.  Each TYPE should be a table of 'target table.
10 -- @@    column'%TYPE indexed by binary_integer. i.e.:
11 -- @@
12 -- @@    TYPE g_<col_name>_type IS TABLE OF
13 -- @@      <target_table>%TYPE
14 -- @@      INDEX BY BINARY_INTEGER;
15 -- @@
16 --
17 TYPE g_organization_id_type IS TABLE OF
18   HRI_CS_PER_ORGCC_CT.organization_id%TYPE
19   INDEX BY BINARY_INTEGER;
20 TYPE g_cost_centre_code_type IS TABLE OF
21   HRI_CS_PER_ORGCC_CT.cost_centre_code%TYPE
22   INDEX BY BINARY_INTEGER;
23 TYPE g_cc_mngr_person_id_type IS TABLE OF
24   HRI_CS_PER_ORGCC_CT.cc_mngr_person_id%TYPE
25   INDEX BY BINARY_INTEGER;
26 TYPE g_effective_start_date_type IS TABLE OF
27   HRI_CS_PER_ORGCC_CT.effective_start_date%TYPE
28   INDEX BY BINARY_INTEGER;
29 TYPE g_effective_end_date_type IS TABLE OF
30   HRI_CS_PER_ORGCC_CT.effective_end_date%TYPE
31   INDEX BY BINARY_INTEGER;
32 TYPE g_company_code_type IS TABLE OF
33   HRI_CS_PER_ORGCC_CT.company_code%TYPE
34   INDEX BY BINARY_INTEGER;
35 TYPE g_reporting_name_type IS TABLE OF
36   HRI_CS_PER_ORGCC_CT.reporting_name%TYPE
37   INDEX BY BINARY_INTEGER;
38 TYPE g_last_change_date_type IS TABLE OF
39   HRI_CS_PER_ORGCC_CT.last_change_date%TYPE
40   INDEX BY BINARY_INTEGER;
41 --
42 -- @@ Code specific to this view/table below ENDS
43 --
44 --
45 -- PLSQL tables representing database table columns
46 --
47 g_organization_id        g_organization_id_type;
48 g_cost_centre_code       g_cost_centre_code_type;
49 g_cc_mngr_person_id      g_cc_mngr_person_id_type;
50 g_effective_start_date   g_effective_start_date_type;
51 g_effective_end_date     g_effective_end_date_type;
52 g_company_code           g_company_code_type;
53 g_reporting_name         g_reporting_name_type;
54 g_last_change_date       g_last_change_date_type;
55 --
56 -- Holds the range for which the collection is to be run.
57 --
58 g_start_date    DATE;
59 g_end_date      DATE;
60 g_full_refresh  VARCHAR2(10);
61 --
62 -- The HRI schema
63 --
64 g_schema                  VARCHAR2(400);
65 --
66 -- Set to true to output to a concurrent log file
67 --
68 g_conc_request_flag       BOOLEAN := FALSE;
69 --
70 -- Number of rows bulk processed at a time
71 --
72 g_chunk_size              PLS_INTEGER;
73 --
74 -- End of time date
75 --
76 -- CONSTANTS
77 -- =========
78 --
79 -- @@ Code specific to this view/table below
80 -- @@ in the call to hri_bpl_conc_log.get_last_collect_to_date
81 -- @@ change param1/2 to be the concurrent program short name,
82 -- @@ and the target table name respectively.
83 --
84 g_target_table          VARCHAR2(30) DEFAULT 'HRI_CS_PER_ORGCC_CT';
85 g_cncrnt_prgrm_shrtnm   VARCHAR2(30) DEFAULT 'HRIPORGC';
86 --
87 -- @@ Code specific to this view/table below ENDS
88 --
89 -- constants that hold the value that indicates to full refresh or not.
90 --
91 g_is_full_refresh    VARCHAR2(5) DEFAULT 'Y';
92 g_not_full_refresh   VARCHAR2(5) DEFAULT 'N';
93 --
94 -- -------------------------------------------------------------------------
95 --
96 -- Inserts row into concurrent program log when the g_conc_request_flag has
97 -- been set to TRUE, otherwise does nothing
98 --
99 PROCEDURE output(p_text  VARCHAR2)
100   IS
101   --
102 BEGIN
103   --
104   -- Write to the concurrent request log if called from a concurrent request
105   --
106   IF (g_conc_request_flag = TRUE) THEN
107     --
108     -- Put text to log file
109     --
110     fnd_file.put_line(FND_FILE.log, p_text);
111     --
112   END IF;
113   --
114 END output;
115 --
116 -- -------------------------------------------------------------------------
117 --
118 -- Recovers rows to insert when an exception occurs
119 --
120 PROCEDURE recover_insert_rows(p_stored_rows_to_insert NUMBER) IS
121 
122 BEGIN
123   --
124   -- loop through rows still to insert one at a time
125   --
126   FOR i IN 1..p_stored_rows_to_insert LOOP
127     --
128     -- Trap unique constraint errors
129     --
130     BEGIN
131       --
132       -- @@ Code specific to this view/table below
133       -- @@ INTRUCTION TO DEVELOPER:
134       -- @@ 1/ For each column in your view put a column in the insert
135       -- @@ statement below.
136       -- @@ 2/ Prefix each column in the VALUE clause with g_
137       -- @@ 3/ make sure (i) is at the end of each column in the value clause
138       --
139       INSERT INTO hri_cs_per_orgcc_ct
140         (organization_id
141         ,cost_centre_code
142         ,cc_mngr_person_id
143         ,effective_start_date
144         ,effective_end_date
145         ,company_code
146         ,reporting_name
147         ,last_change_date)
148       VALUES
149         (g_organization_id(i)
150         ,g_cost_centre_code(i)
151         ,g_cc_mngr_person_id(i)
152         ,g_effective_start_date(i)
153         ,g_effective_end_date(i)
154         ,g_company_code(i)
155         ,g_reporting_name(i)
156         ,g_last_change_date(i));
157       --
158       -- @@Code specific to this view/table below ENDS
159       --
160     EXCEPTION
161       --
162       WHEN OTHERS THEN
163         --
164         -- Probable overlap on date tracked assignment rows
165         --
166         output('Single insert error: ' || to_char(g_organization_id(i)) ||
167                ' - ' || to_char(g_cc_mngr_person_id(i)));
168         --
169         output(sqlerrm);
170         output(sqlcode);
171         --
172       --
173     END;
174     --
175   END LOOP;
176   --
177   COMMIT;
178   --
179 END recover_insert_rows;
180 --
181 -- -------------------------------------------------------------------------
182 --
183 -- Bulk inserts rows from global temporary table to database table
184 --
185 PROCEDURE bulk_insert_rows(p_stored_rows_to_insert NUMBER) IS
186   --
187 BEGIN
188   --
189   -- insert chunk of rows
190   --
191   -- @@ Code specific to this view/table below
192   -- @@ INTRUCTION TO DEVELOPER:
193   -- @@ 1/ For each column in your view put a column in the insert statement
194   --       below.
195   -- @@ 2/ Prefix each column in the VALUE clause with g_
196   -- @@ 3/ make sure (i) is at the end of each column in the value clause
197   --
198   FORALL i IN 1..p_stored_rows_to_insert
199       INSERT INTO hri_cs_per_orgcc_ct
200         (organization_id
201         ,cost_centre_code
202         ,cc_mngr_person_id
203         ,effective_start_date
204         ,effective_end_date
205         ,company_code
206         ,reporting_name
207         ,last_change_date)
208       VALUES
209         (g_organization_id(i)
210         ,g_cost_centre_code(i)
211         ,g_cc_mngr_person_id(i)
212         ,g_effective_start_date(i)
213         ,g_effective_end_date(i)
214         ,g_company_code(i)
215         ,g_reporting_name(i)
216         ,g_last_change_date(i));
217   --
218   -- @@Code specific to this view/table below ENDS
219   --
220   -- commit the chunk of rows
221   --
222   COMMIT;
223   --
224 EXCEPTION
225   --
226   WHEN OTHERS THEN
227     --
228     -- Probable unique constraint error
229     --
230     ROLLBACK;
231     --
232     recover_insert_rows(p_stored_rows_to_insert);
233     --
234   --
235 END bulk_insert_rows;
236 --
237 -- -------------------------------------------------------------------------
238 --
239 -- Loops through table and collects into table structure.
240 --
241 PROCEDURE Incremental_Update IS
242   --
243 BEGIN
244   --
245   -- @@ Code specific to this view/table below
246   -- @@ INTRUCTION TO DEVELOPER:
247   -- @@ 1/ Change the code below to reflect the columns in your view / table
248   -- @@ 2/ Change the FROM, INSERT, DELETE statements to point at the relevant
249   -- @@    source view / table
250   --
251   -- Insert completly new rows
252   --
253   -- log('Doing insert.');
254   INSERT INTO hri_cs_per_orgcc_ct
255   (organization_id
256   ,cost_centre_code
257   ,cc_mngr_person_id
258   ,effective_start_date
259   ,effective_end_date
260   ,company_code
261   ,reporting_name
262   ,last_change_date)
263   SELECT
264    organization_id
265   ,cost_centre_code
266   ,cc_mngr_person_id
267   ,effective_start_date
268   ,effective_end_date
269   ,company_code
270   ,reporting_name
271   ,last_change_date
272   FROM hri_cs_per_orgcc_v svw
273   --
274   -- 4303724, Used TRUNC function
275   --
276   WHERE TRUNC(last_change_date) BETWEEN g_start_date
277                                 AND     g_end_date
278   AND NOT EXISTS (SELECT 'x'
279                   FROM   hri_cs_per_orgcc_ct tbl
280                   WHERE  svw.organization_id    = tbl.organization_id
281                   AND    svw.effective_start_date   = tbl.effective_start_date
282                   AND    svw.effective_end_date     = tbl.effective_end_date);
283   -- log('Insert >'||TO_CHAR(sql%rowcount));
284   -- log('Doing update.');
285   --
286   -- Update changed rows
287   -- Bug 3658494: Query made performant
288   --
289   UPDATE hri_cs_per_orgcc_ct tbl
290     SET (organization_id
291         ,cost_centre_code
292         ,cc_mngr_person_id
293         ,effective_start_date
294         ,effective_end_date
295         ,company_code
296         ,reporting_name
297         ,last_change_date) =
298           (SELECT svw.organization_id
299                  ,svw.cost_centre_code
300                  ,svw.cc_mngr_person_id
301                  ,svw.effective_start_date
302                  ,svw.effective_end_date
303                  ,svw.company_code
304                  ,svw.reporting_name
305                  ,svw.last_change_date
306            FROM hri_cs_per_orgcc_v     svw
307 	   --
308 	   -- 4303724, Used TRUNC function
309 	   --
310            WHERE TRUNC(svw.last_change_date) BETWEEN g_start_date
311                                              AND     g_end_date
312            AND   svw.organization_id        = tbl.organization_id
313            AND   svw.effective_start_date   = tbl.effective_start_date
314            AND   svw.effective_end_date     = tbl.effective_end_date
315            )
316     WHERE (tbl.organization_id,
317            tbl.effective_start_date,
318            tbl.effective_end_date)
319           IN
320           (SELECT svw.organization_id,
321                   svw.effective_start_date,
322                   svw.effective_end_date
323            FROM   hri_cs_per_orgcc_v     svw
324 	   --
325 	   -- 4303724, Used TRUNC function
326 	   --
327            WHERE  TRUNC(svw.last_change_date) BETWEEN g_start_date
328                                               AND     g_end_date);
329   --
330   -- log('Update >'||TO_CHAR(sql%rowcount));
331   --
332   -- Delete rows that no longer exist in the source view.
333   --
334   -- log('Doing delete.');
335   DELETE
336   FROM hri_cs_per_orgcc_ct tbl
337   WHERE NOT EXISTS (SELECT 'x'
338                     FROM  hri_cs_per_orgcc_v svw
339                     WHERE svw.organization_id      = tbl.organization_id
340                     AND   svw.effective_start_date = tbl.effective_start_date
341                     AND   svw.effective_end_date   = tbl.effective_end_date);
342   -- log('Delete >'||TO_CHAR(sql%rowcount));
343   --
344   -- @@ Code specific to this view/table below ENDS
345   --
346   COMMIT;
347   -- log('Done incremental update.');
348   --
349 EXCEPTION
350   --
351   WHEN OTHERS THEN
352     --
353     Output('Failure in incremental update process.');
354     --
355     RAISE;
356     --
357   --
358 END;
359 --
360 -- -------------------------------------------------------------------------
361 --
362 --
363 -- Loops through table and collects into table structure.
364 --
365 PROCEDURE Full_Refresh IS
366   --
367   -- Select all from the source view for materialization
368   --
369   -- @@ Code specific to this view/table below
370   -- @@ INTRUCTION TO DEVELOPER:
371   -- @@ 1/ Change the select beloe to select all the columns from your view
372   -- @@ 2/ Change the FROM statement to point at the relevant source view
373   --
374   CURSOR source_view_csr IS
375   SELECT
376      organization_id
377     ,cost_centre_code
378     ,cc_mngr_person_id
379     ,effective_start_date
380     ,effective_end_date
381     ,company_code
382     ,reporting_name
383     ,last_change_date
384   FROM hri_cs_per_orgcc_v svw;
385   --
386   -- @@Code specific to this view/table below ENDS
387   --
388   l_exit_main_loop       BOOLEAN := FALSE;
389   l_rows_fetched         PLS_INTEGER := g_chunk_size;
390   l_sql_stmt      VARCHAR2(2000);
391   --
392 BEGIN
393   -- log('here ...');
394   --
395   -- Truncate the target table prior to full refresh.
396   --
397   l_sql_stmt := 'TRUNCATE TABLE ' || g_schema || '.'||g_target_table;
398   -- log('>'||l_sql_stmt||'<');
399   --
400   EXECUTE IMMEDIATE(l_sql_stmt);
401   -- log('trunced ...');
402   --
403   -- Write timing information to log
404   --
405   output('Truncated the table:   '  ||
406          to_char(sysdate,'HH24:MI:SS'));
407   --
408   -- open main cursor
409   --
410   -- log('open cursor ...');
411   OPEN source_view_csr;
412   --
413   <<main_loop>>
414   LOOP
415     --
416     -- bulk fetch rows limit the fetch to value of g_chunk_size
417     --
418     -- @@ Code specific to this view/table below
419     -- @@ INTRUCTION TO DEVELOPER:
420     -- @@ Change the bulk collect below to select all the columns from your
421     -- @@ view
422     --
423     -- log('start fetch ...');
424     -- log('>'||TO_CHAR(g_chunk_size)||'<');
425     FETCH source_view_csr
426     BULK COLLECT INTO
427        g_organization_id
428       ,g_cost_centre_code
429       ,g_cc_mngr_person_id
430       ,g_effective_start_date
431       ,g_effective_end_date
432       ,g_company_code
433       ,g_reporting_name
434       ,g_last_change_date
435     LIMIT g_chunk_size;
436     -- log('finish fetch ...');
437     --
438     -- @@Code specific to this view/table below ENDS
439     --
440     -- check to see if the last row has been fetched
441     --
442     IF source_view_csr%NOTFOUND THEN
443       --
444       -- last row fetched, set exit loop flag
445       --
446       l_exit_main_loop := TRUE;
447       --
448       -- do we have any rows to process?
449       --
450       l_rows_fetched := MOD(source_view_csr%ROWCOUNT,g_chunk_size);
451       --
452       -- note: if l_rows_fetched > 0 then more rows are required to be
453       -- processed and the l_rows_fetched will contain the exact number of
454       -- rows left to process
455       --
456       IF l_rows_fetched = 0 THEN
457         --
458         -- no more rows to process so exit loop
459         --
460         EXIT main_loop;
461       END IF;
462     END IF;
463     --
464     -- bulk insert rows processed so far
465     --
466     -- log('call bulk ...');
467     bulk_insert_rows (l_rows_fetched);
468     -- log('end bulk ...');
469     --
470     -- exit loop if required
471     --
472     IF l_exit_main_loop THEN
473       --
474       EXIT main_loop;
475       --
476     END IF;
477     --
478   END LOOP;
479   --
480   CLOSE source_view_csr;
481   --
482   -- log('End ...');
483 EXCEPTION
484   WHEN OTHERS THEN
485     --
486     -- unexpected error has occurred so close down
487     -- main bulk cursor if it is open
488     --
489     IF source_view_csr%ISOPEN THEN
490       --
491       CLOSE source_view_csr;
492       --
493     END IF;
494     --
495     -- re-raise error
496     RAISE;
497     --
498   --
499 END Full_Refresh;
500 --
501 -- -------------------------------------------------------------------------
502 -- Checks what mode you are running in, and if g_full_refresh =
503 -- g_is_full_refresh calls
504 -- Full_Refresh procedure, otherwise Incremental_Update is called.
505 --
506 PROCEDURE Collect IS
507   --
508 BEGIN
509   --
510   -- If in full refresh mode chnage the dates so that the collection history
511   -- is correctly maintained.
512   --
513   IF g_full_refresh = g_is_full_refresh THEN
514     --
515     g_start_date   := hr_general.start_of_time;
516     g_end_date     := SYSDATE;
517     --
518     -- log('Doing full refresh.');
519     Full_Refresh;
520     --
521   ELSE
522     --
523     -- log('Doing incremental update.');
524     --
525     -- If the passed in date range is NULL default it.
526     --
527     IF g_start_date IS NULL OR
528        g_end_date   IS NULL
529     THEN
530     -- log('Input dates NULL.');
531       --
532       g_start_date   :=  fnd_date.displaydt_to_date(
533                                   hri_bpl_conc_log.get_last_collect_to_date(
534                                         g_cncrnt_prgrm_shrtnm
535                                        ,g_target_table));
536       --
537       g_end_date     := SYSDATE;
538       -- log('start >'||TO_CHAR(g_start_date));
539       -- log('end >'||TO_CHAR(g_end_date));
540       -- log('Defaulted input DATES.');
541       --
542     END IF;
543     --
544     -- log('Calling incremenatal update.');
545     Incremental_Update;
546     -- log('Called incremenatal update.');
547     --
548   END IF;
549   --
550 END Collect;
551 --
552 -- -------------------------------------------------------------------------
553 -- Checks if the Target table is Empty
554 --
555 FUNCTION Target_table_is_Empty RETURN BOOLEAN IS
556   --
557   -- @@ Code specific to this view/table below
558   -- @@ INTRUCTION TO DEVELOPER:
559   -- @@ Change the table in the FROM clause below to be the same as  your
560   -- @@ target table.
561   --
562   CURSOR csr_recs_exist IS
563   SELECT 'x'
564   FROM   hri_cs_per_orgcc_ct;
565   --
566   -- @@ Code specific to this view/table ENDS
567   --
568   l_exists_chr    VARCHAR2(1);
569   l_exists        BOOLEAN;
570   --
571 BEGIN
572   --
573   OPEN csr_recs_exist;
574   --
575   FETCH csr_recs_exist INTO l_exists_chr;
576   --
577   IF (csr_recs_exist%NOTFOUND)
578   THEN
579     --
580     l_exists := TRUE;
581     -- log('no data in table');
582     --
583   ELSE
584     --
585     l_exists := FALSE;
586     -- log('data is in table');
587     --
588   END IF;
589   --
590   CLOSE csr_recs_exist;
591   --
592   RETURN l_exists;
593   --
594 EXCEPTION
595   --
596   WHEN OTHERS
597   THEN
598     --
599     CLOSE csr_recs_exist;
600     RAISE;
601     --
602   --
603 END Target_table_is_Empty;
604 --
605 -- -------------------------------------------------------------------------
606 --
607 -- Main entry point to load the table.
608 --
609 PROCEDURE Load(p_chunk_size    IN NUMBER,
610                p_start_date    IN VARCHAR2,
611                p_end_date      IN VARCHAR2,
612                p_full_refresh  IN VARCHAR2) IS
613   --
614   -- Variables required for table truncation.
615   --
616   l_dummy1        VARCHAR2(2000);
617   l_dummy2        VARCHAR2(2000);
618   --
619 BEGIN
620   --
621   output('PL/SQL Start:   ' || to_char(sysdate,'HH24:MI:SS'));
622   --
623   -- Set globals
624   --
625   g_start_date := to_date(p_start_date, 'YYYY/MM/DD HH24:MI:SS');
626   g_end_date   := to_date(p_end_date,   'YYYY/MM/DD HH24:MI:SS');
627   --
628   IF p_chunk_size IS NULL
629   THEN
630     --
631     g_chunk_size := 500;
632     --
633   ELSE
634     --
635     g_chunk_size   := p_chunk_size;
636     --
637   END IF;
638   --
639   IF p_full_refresh IS NULL
640   THEN
641     --
642     g_full_refresh := g_not_full_refresh;
643     --
644   ELSE
645     --
646     g_full_refresh := p_full_refresh;
647     --
648   END IF;
649   --
650   -- If the target table is empty default to full refresh.
651   --
652   IF Target_table_is_Empty
653   THEN
654     --
655     output('Target table '||g_target_table||
656            ' is empty, so doing a full refresh.');
657     -- log('Doing a full refresh....');
658     --
659     g_full_refresh := g_is_full_refresh;
660     --
661   END IF;
662   --
663   -- log('p_chunk_size>'||TO_CHAR(g_chunk_size)||'<');
664   -- Find the schema we are running in.
665   --
666   IF NOT fnd_installation.get_app_info('HRI',l_dummy1, l_dummy2, g_schema)
667   THEN
668     --
669     -- Could not find the schema raising exception.
670     --
671     output('Could not find schema to run in.');
672     --
673     -- log('Could not find schema.');
674     RAISE NO_DATA_FOUND;
675     --
676   END IF;
677   --
678   -- Update information about collection
679   --
680   -- log('Record process start.');
681   /* double check correct val passed in below */
682   hri_bpl_conc_log.record_process_start(g_cncrnt_prgrm_shrtnm);
683   --
684   -- Time at start
685   --
686   -- log('collect.');
687   --
688   -- Get HRI schema name - get_app_info populates l_schema
689   --
690   -- Insert new records
691   --
692   collect;
693   -- log('collectED.');
694   --
695   -- Write timing information to log
696   --
697   output('Finished changes to the table:  '  ||
698          to_char(sysdate,'HH24:MI:SS'));
699   --
700   -- Gather index stats
701   --
702   -- log('gather stats.');
703   fnd_stats.gather_table_stats(g_schema, g_target_table);
704   --
705   -- Write timing information to log
706   --
707   output('Gathered stats:   '  ||
708          to_char(sysdate,'HH24:MI:SS'));
709   --
710   -- log('log end.');
711   hri_bpl_conc_log.log_process_end(
712         p_status         => TRUE,
713         p_period_from    => TRUNC(g_start_date),
714         p_period_to      => TRUNC(g_end_date),
715         p_attribute1     => p_full_refresh,
716         p_attribute2     => p_chunk_size);
717   -- log('-END-');
718   --
719 EXCEPTION
720   --
721   WHEN OTHERS
722   THEN
723     --
724     ROLLBACK;
725     RAISE;
726     --
727   --
728 END Load;
729 --
730 -- -------------------------------------------------------------------------
731 --
732 -- Entry point to be called from the concurrent manager
733 --
734 PROCEDURE Load(errbuf          OUT NOCOPY VARCHAR2,
735                retcode         OUT NOCOPY VARCHAR2,
736                p_chunk_size    IN NUMBER,
737                p_start_date    IN VARCHAR2,
738                p_end_date      IN VARCHAR2,
739                p_full_refresh  IN VARCHAR2)
740 IS
741   --
742 BEGIN
743   --
744   -- Enable output to concurrent request log
745   --
746   g_conc_request_flag := TRUE;
747   --
748   load(p_chunk_size   => p_chunk_size,
749        p_start_date   => p_start_date,
750        p_end_date     => p_end_date,
751        p_full_refresh => p_full_refresh);
752   --
753 EXCEPTION
754   --
755   WHEN OTHERS THEN
756     --
757     errbuf  := SQLERRM;
758     retcode := SQLCODE;
759     --
760   --
761 END load;
762 --
763 END HRI_OPL_PER_ORGCC;