DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_OPL_GEO_LOCHR

Source


1 PACKAGE BODY HRI_OPL_GEO_LOCHR AS
2 /* $Header: hripglh.pkb 120.8 2006/10/11 15:34:48 jtitmas noship $ */
3 --
4 -- Holds the range for which the collection is to be run.
5 --
6 g_start_date                  DATE;
7 g_end_date                    DATE;
8 g_full_refresh                VARCHAR2(10);
9 --
10 -- The HRI schema
11 --
12 g_schema                      VARCHAR2(400);
13 --
14 -- 115.15 4278978
15 -- created as globals as require these in each collection procedure
16 -- user calling the load proces used in who columnc
17 g_user_id                     NUMBER  DEFAULT -1;
18 -- Start time of load process used in who columns
19 g_current_time                DATE    DEFAULT SYSDATE;
20 --
21 -- General purpose sql string buffer
22 --  saves having to re-declare in each local proc
23 g_sql_stmt                    VARCHAR2(2000);
24 --
25 -- Bug 4105868: Global to store msg_sub_group
26 --
27 g_msg_sub_group               VARCHAR2(400) := '';
28 --
29 -- Global DBI collection start date initialization
30 --
31 g_dbi_collection_start_date DATE := TRUNC(TO_DATE(fnd_profile.value
32                                         ('BIS_GLOBAL_START_DATE'),'MM/DD/YYYY'));
33 --
34 -- CONSTANTS
35 -- =========
36 --
37 -- @@ Code specific to this view/table below
38 -- @@ in the call to hri_bpl_conc_log.get_last_collect_to_date
39 -- @@ change param1/2 to be the concurrent program short name,
40 -- @@ and the target table name respectively.
41 --
42 -- 115.15 4278978
43 -- New tables
44 -- changed data types to constants from defaults
45 g_target_lochr_table          CONSTANT VARCHAR2(30) := 'HRI_CS_GEO_LOCHR_CT';
46 g_target_region_table         CONSTANT VARCHAR2(30) := 'HRI_CS_GEO_REGION_CT';
47 g_target_country_table        CONSTANT VARCHAR2(30) := 'HRI_CS_GEO_COUNTRY_CT';
48 --
49 g_cncrnt_prgrm_shrtnm         CONSTANT VARCHAR2(30) := 'HRIGLOCHR';
50 --
51 -- @@ Code specific to this view/table below ENDS
52 -- constants that hold the value that indicates to full refresh or not.
53 --
54 g_is_full_refresh    VARCHAR2(5) DEFAULT 'Y';
55 g_not_full_refresh   VARCHAR2(5) DEFAULT 'N';
56 --
57 -- -------------------------------------------------------------------------
58 -- Inserts row into concurrent program log when the g_conc_request_flag has
59 -- been set to TRUE, otherwise does nothing
60 -- -------------------------------------------------------------------------
61 --
62 PROCEDURE output(p_text  VARCHAR2) IS
63 --
64 BEGIN
65   --
66   -- Bug 4105868: Global to store msg_sub_group
67   --
68   HRI_BPL_CONC_LOG.output(p_text);
69   --
70 END output;
71 --
72 -- -------------------------------------------------------------------------
73 -- Inserts row into concurrent program log if debugging is enabled
74 -- -------------------------------------------------------------------------
75 --
76 PROCEDURE dbg(p_text  VARCHAR2) IS
77 --
78 BEGIN
79   --
80   -- Bug 4105868: Collection Diagnostics
81   --
82   HRI_BPL_CONC_LOG.dbg(p_text);
83   --
84 END dbg;
85 --
86 -- -----------------------------------------------------------------------------
87 -- Inserts row into concurrent program log if debugging is enabled
88 -- -----------------------------------------------------------------------------
89 --
90 PROCEDURE dbg_time(p_text  VARCHAR2) IS
91 --
92 BEGIN
93   --
94   -- Bug 4105868: Collection Diagnostics
95   --
96   dbg(' *TIME* :'|| to_char(SYSDATE, 'HH24:MI:SS') ||' -> '||p_text);
97   --
98 END dbg_time;
99 --
100 -- -----------------------------------------------------------------------------
101 -- 3601662
102 -- Runs given sql statement dynamically without raising an error
103 -- -----------------------------------------------------------------------------
104 --
105 PROCEDURE run_sql_stmt_noerr(p_sql_stmt   VARCHAR2) IS
106 --
107 BEGIN
108   --
109   dbg('Commencing -> run_sql_stmt_noerr');
110   --
111   EXECUTE IMMEDIATE p_sql_stmt;
112   --
113   dbg('Exiting -> run_sql_stmt_noerr');
114   --
115 EXCEPTION
116   --
117   WHEN OTHERS THEN
118     --
119     dbg('Error running sql:');
120     output(SUBSTR(p_sql_stmt,1,230));
121     --
122     -- Bug 4105868: Collection Diagnostic Call
123     --
124     hri_bpl_conc_log.log_process_info
125             (p_package_name      => 'HRI_OPL_GEO_LOCHR'
126             ,p_msg_type          => 'WARNING'
127             ,p_msg_group         => 'GEOGRAPHY'
128             ,p_msg_sub_group     => 'RUN_SQL_STMT_NOERR'
129             ,p_sql_err_code      => SQLCODE
130             ,p_note              => SUBSTR(p_sql_stmt,1, 3900));
131     --
132 END run_sql_stmt_noerr;
133 --
134 -- -----------------------------------------------------------------------------
135 -- Checks if the Target table is Empty
136 -- -----------------------------------------------------------------------------
137 --
138 FUNCTION Target_table_is_Empty RETURN BOOLEAN IS
139   --
140   -- @@ Code specific to this view/table below
141   -- @@ INTRUCTION TO DEVELOPER:
142   -- @@ Change the table in the FROM clause below to be the same as  your
143   -- @@ target table.
144   --
145   -- Bug 2834228 added rownum condition to stop FTS
146   --
147   CURSOR csr_recs_exist IS
148   SELECT 'x'
149   FROM   hri_cs_geo_lochr_ct
150   WHERE  rownum < 2;
151   --
152   -- @@ Code specific to this view/table ENDS
153   --
154   l_exists_chr    VARCHAR2(1);
155   l_exists        BOOLEAN;
156   --
157 BEGIN
158   --
159   dbg('Commencing -> Target_table_is_Empty');
160   --
161   OPEN csr_recs_exist;
162   --
163   FETCH csr_recs_exist INTO l_exists_chr;
164   --
165   IF (csr_recs_exist%NOTFOUND) THEN
166     --
167     l_exists := TRUE;
168     --
169    dbg('no data in table hri_cs_geo_lochr_ct');
170     --
171   ELSE
172     --
173     l_exists := FALSE;
174     --
175     dbg('data exists in table hri_cs_geo_lochr_ct');
176     --
177   END IF;
178   --
179   CLOSE csr_recs_exist;
180   --
181   dbg('Exiting -> Target_table_is_Empty');
182   --
183   RETURN l_exists;
184   --
185 EXCEPTION
186   --
187   WHEN OTHERS THEN
188     --
189     IF csr_recs_exist%ISOPEN THEN
190       --
191       CLOSE csr_recs_exist;
192       --
193     END IF;
194     --
195     -- Bug 4105868: Collection Diagnostics
196     --
197     g_msg_sub_group := NVL(g_msg_sub_group, 'TARGET_TABLE_IS_EMPTY');
198     --
199     RAISE;
200     --
201   --
202 END Target_table_is_Empty;
203 --
204 -- -----------------------------------------------------------------------------
205 --
206 -- INCREMENTAL REFRESH PROCEDURES
207 --
208 -- -----------------------------------------------------------------------------
209 -- Procedure to incremental refresh the location structure table
210 -- -----------------------------------------------------------------------------
211 PROCEDURE Incr_Refresh_Lochr_Struct IS
212  --
213  -- PL/SQL table of updated location records
214  TYPE l_number_tab_type IS TABLE OF hri_cs_geo_lochr_ct.location_id%TYPE;
215  l_upd_location_ids        L_NUMBER_TAB_TYPE;
216  --
217 BEGIN
218   --
219   dbg('Commencing -> Incremental Refresh LocHR Struct');
220   --
221   dbg(' Table:'||g_schema||'.'||g_target_lochr_table);
222   --
223   dbg_time('Insert Start');
224   INSERT
225   INTO   hri_cs_geo_lochr_ct
226          (area_code
227          ,country_code
228          ,region_code
229          ,city_cid
230          ,location_id
231          ,geo_area_id
232          ,geo_country_id
233          ,geo_region_id
234          ,city_src_town_or_city_txt
235          ,effective_start_date
236          ,effective_end_date
237          ,business_group_id
238          ,last_change_date
239          )
240   SELECT area_code,
241          country_code,
242          region_code,
243          city_cid,
244          location_id,
245          geo_area_id,
246          geo_country_id,
247          geo_region_id,
248          city_src_town_or_city_txt,
249          effective_start_date,
250          effective_end_date,
251          business_group_id,
252          NVL(last_change_date, g_dbi_collection_start_date)
253   FROM   hri_cs_geo_lochr_v svw
254   --
255   -- 4303724, Used TRUNC function
256   --
257   WHERE  TRUNC(last_change_date) BETWEEN g_start_date
258                                  AND     g_end_date
259   AND    NOT EXISTS (SELECT 'x'
260                      FROM   hri_cs_geo_lochr_ct tbl
261                      WHERE  svw.location_id        = tbl.location_id
262                      AND    effective_start_date   = tbl.effective_start_date
263                      AND    effective_end_date     = tbl.effective_end_date)
264   ;
265   dbg_time('Insert End');
266   --
267   dbg('Insert >'||TO_CHAR(sql%rowcount));
268   --
269   dbg_time('Update Start');
270   --
271   -- UPDATE -> Rows where PK has stayed the same but other attributes / parents
272   --           have changed
273   --           Results from -> Regions that have had any of these change:
274   --             1) Area changed
275   --             2) Country changed
276   --             3) Region changed
277   --             4) City changed
278   --
279   -- 4546781 - JRHyde
280   -- Change the where predicate to test all FKS for changes not just PK
281   -- Removed the date clause as a delete will not give a date hence
282   --  last_change_date is effectively useless
283   -- Removed effective start and end date predicate as the dimension is not
284   -- slowly changing - if it was then the PK index should be composite.
285   --
286   UPDATE hri_cs_geo_lochr_ct tbl
287     SET
288     (       area_code
289            ,country_code
290            ,region_code
291            ,city_cid
292            ,location_id
293            ,geo_area_id
294            ,geo_country_id
295            ,geo_region_id
296            ,city_src_town_or_city_txt
297            ,effective_start_date
298            ,effective_end_date
299            ,business_group_id
300            ,last_change_date
301     ) =
302     (SELECT svw.area_code,
303             svw.country_code,
304             svw.region_code,
305             svw.city_cid,
306             svw.location_id,
307             svw.geo_area_id,
308             svw.geo_country_id,
309             svw.geo_region_id,
310             svw.city_src_town_or_city_txt,
311             svw.effective_start_date,
312             svw.effective_end_date,
313             svw.business_group_id,
314             NVL(svw.last_change_date, g_dbi_collection_start_date)
315        FROM hri_cs_geo_lochr_v svw
316       WHERE svw.location_id            = tbl.location_id
317         AND (   svw.area_code         <> tbl.area_code
318              OR svw.country_code      <> tbl.country_code
319              OR svw.region_code       <> tbl.region_code
320              OR svw.city_cid          <> tbl.city_cid
321             )
322     )
323   WHERE EXISTS
324         (SELECT 'X'
325            FROM hri_cs_geo_lochr_v     svw
326           WHERE svw.location_id            = tbl.location_id
327             AND svw.effective_start_date   = tbl.effective_start_date
328             AND svw.effective_end_date     = tbl.effective_end_date
329             AND (   svw.area_code         <> tbl.area_code
330                  OR svw.country_code      <> tbl.country_code
331                  OR svw.region_code       <> tbl.region_code
332                  OR svw.city_cid          <> tbl.city_cid
333                 )
334         )
335   RETURNING tbl.location_id BULK COLLECT INTO l_upd_location_ids
336   ;
337   dbg_time('Update End');
338   --
339   dbg('Update >'||TO_CHAR(sql%rowcount));
340   --
341   -- DELETE -> PKs / Rows that are old
342   --           , i.e. in table but no longer in source view
343   --           Results from -> All hr locations deleted
344   --
345   dbg_time('Delete Start');
346   DELETE
347     FROM hri_cs_geo_lochr_ct tbl
348    WHERE NOT EXISTS
349          (SELECT 'x'
350             FROM hri_cs_geo_lochr_v svw
351            WHERE svw.location_id          = tbl.location_id
352          )
353   ;
354   dbg_time('Delete End');
355   --
356   dbg('Delete >'||TO_CHAR(sql%rowcount));
357   --
358   dbg('Commiting');
359   COMMIT;
360   --
361   -- If the location details of any of the existing records is changed then
362   -- the corresponding changes should be reflected in the assingment delta table
363   -- also.
364   -- So insert the LOCATION_ID of the updated records into the assingment delta
365   -- table so that the changes can be made to the assignment delta table by the
366   -- incr process
367   --
368   -- NOTE: JUSTIN HYDE 30th August 2005
369   -- This is not a scaleable design. As each new fact will require the dimension
370   -- to be updated to insert into their respective EQ.  Suggest this needs to be
371   -- a passive model not an active model and hence the dimension pushes to 1
372   --  event queue only and that can be reference / subscribed to base on the
373   -- fact and the customers subscription to dimensions usage in the fact.
374   -- Suggest we need to put this in a dimension change table
375   -- this is a bit like an MV log :-)
376   -- The alternative is a single event repository but I get the feeling indexing
377   -- on such a 'flexible' repository may be a nightmare.
378   -- Perhaps also flagging at what level the change occurs from, so as to not
379   -- have to change the levels that don't reflect that level FK in them
380   --
381   dbg_time('Update Event Queue Start');
382   IF (l_upd_location_ids.LAST > 0 AND
383       fnd_profile.value('HRI_IMPL_DBI') = 'Y') THEN
384       --
385       BEGIN
386         --
387         FORALL i IN 1..l_upd_location_ids.LAST SAVE EXCEPTIONS
388           INSERT INTO HRI_EQ_ASG_SUP_WRFC
389            (SOURCE_TYPE,
390             SOURCE_ID)
391         VALUES
392            ('LOCATION',
393             l_upd_location_ids(i));
394         --
395       EXCEPTION WHEN OTHERS THEN
396         --
397         dbg(sql%bulk_exceptions.COUNT
398             || ' location records already exists in the event queue ');
399         --
400       END;
401       -- Commit changes
402       COMMIT;
403       --
404     END IF;
405   dbg_time('Update Event Queue End');
406   --
407   dbg('Exiting -> Incremental Refresh LocHR Struct');
408   --
409 EXCEPTION
410   --
411   WHEN OTHERS THEN
412     --
413     output('Failure in location structure incremental refresh process.');
414     output(SQLERRM);
415     -- Bug 4105868: Collection Diagnostic
416     g_msg_sub_group := NVL(g_msg_sub_group, 'INCR_REFRESH_LOCHR_STRUCT');
417     --
418     --   115.15 - 4278978: Require rollbacks for each structure collection
419     ROLLBACK;
420     --
421     RAISE;
422     --
423   --
424 END Incr_Refresh_Lochr_Struct;
425 -- -----------------------------------------------------------------------------
426 -- Procedure to incremental refresh the region structure table
427 -- -----------------------------------------------------------------------------
428 PROCEDURE Incr_Refresh_Region_Struct
429   IS
430 BEGIN
431   --
432   dbg('Commencing -> Incremental Refresh Region Structure');
433   --
434   dbg(' Table:'||g_schema||'.'||g_target_region_table);
435   --
436   dbg_time('Update Start');
437   --
438   -- UPDATE -> Rows where PK has stayed the same but other attributes / parents
439   --           have changed
440   --           Results from -> Regions that have had any of these change:
441   --             1) Area changed
442   --             2) Country changed
443   --             3) Start Date
444   --             4) End Date
445   -- 4546781
446   -- Changed predicates of set select statement where and update where clause.
447   --
448   UPDATE hri_cs_geo_region_ct tbl
449     SET
450    (       geo_area_code
451          , geo_country_code
452          , geo_region_code
453          , geo_region_sk_pk
454          , start_date
455          , end_date
456          , last_change_date
457    ) =
458    (SELECT csr.geo_area_code
459          , csr.geo_country_code
460          , csr.geo_region_code
461          , csr.geo_region_sk_pk
462          , csr.start_date
463          , csr.end_date
464          , csr.last_change_date
465       FROM hri_dbi_cs_geo_region_v     csr
466      WHERE csr.geo_region_sk_pk       = tbl.geo_region_sk_pk
467        AND (   csr.geo_area_code     <> tbl.geo_area_code
468             OR csr.geo_country_code  <> tbl.geo_country_code
469             OR csr.start_date        <> tbl.start_date
470             OR csr.end_date          <> tbl.end_date
471            )
472    )
473    WHERE EXISTS
474          (SELECT 'X'
475             FROM hri_dbi_cs_geo_region_v csr
476            WHERE csr.geo_region_sk_pk       = tbl.geo_region_sk_pk
477              AND (   csr.geo_area_code     <> tbl.geo_area_code
478                   OR csr.geo_country_code  <> tbl.geo_country_code
479                   OR csr.start_date        <> tbl.start_date
480                   OR csr.end_date          <> tbl.end_date
481                  )
482          )
483   ;
484   dbg_time('Update End');
485   --
486   dbg('Update >'||TO_CHAR(sql%rowcount));
487   --
488   -- DELETE -> PKs / Rows that are old
489   --           , i.e. in table but no longer in source view
490   --           Results from -> Regions being removed for all hr locations, via:
491   --             1) Location attribution to Region
492   --
493   dbg_time('Delete Start');
494   DELETE
495     FROM hri_cs_geo_region_ct tbl
496    WHERE NOT EXISTS
497          (SELECT 'X'
498             FROM hri_dbi_cs_geo_region_v csr
499            WHERE csr.geo_region_sk_pk       = tbl.geo_region_sk_pk
500          )
501   ;
502   dbg_time('Delete End');
503   --
504   dbg('Delete >'||TO_CHAR(sql%rowcount));
505   --
506   -- INSERT -> PKs / Rows that are new
507   --           , i.e. in source view but not so far in the table
508   --           Results from -> New Regions being brought in via:
509   --             1) Location attribution to Region
510   --
511   dbg_time('Insert Start');
512   INSERT
513       INTO hri_cs_geo_region_ct
514          ( geo_area_code
515          , geo_country_code
516          , geo_region_code
517          , geo_region_sk_pk
518          , start_date
519          , end_date
520          , last_change_date
521          )
522     SELECT csr.geo_area_code
523          , csr.geo_country_code
524          , csr.geo_region_code
525          , csr.geo_region_sk_pk
526          , csr.start_date
527          , csr.end_date
528          , csr.last_change_date
529       FROM hri_dbi_cs_geo_region_v csr
530      WHERE NOT EXISTS
531            (SELECT 'x'
532               FROM hri_cs_geo_region_ct tbl
533              WHERE csr.geo_region_sk_pk       = tbl.geo_region_sk_pk
534            )
535   ;
536   dbg_time('Insert End');
537   --
538   dbg('Insert >'||TO_CHAR(sql%rowcount));
539   --
540   -- @@ Code specific to this view/table below ENDS
541   --
542   dbg('Committing');
543   COMMIT;
544   --
545   dbg('Exiting -> Incremental Refresh Region Structure');
546   --
547 EXCEPTION
548   --
549   WHEN OTHERS THEN
550     --
551     Output('Failure in region structure incremental update process.');
552     output(SQLERRM);
553     --
554     g_msg_sub_group := NVL(g_msg_sub_group, 'INCR_REFRESH_REGION_STRUCT');
555     --
556     ROLLBACK;
557     --
558     RAISE;
559     --
560   --
561 END Incr_Refresh_Region_Struct;
562 -- -----------------------------------------------------------------------------
563 -- Procedure to Incremental Refresh the country structure table
564 -- -----------------------------------------------------------------------------
565 PROCEDURE Incr_Refresh_Country_Struct
566   IS
567 BEGIN
568   --
569   dbg('Commencing -> Incremental refresh of Country Structure');
570   --
571   dbg(' Table:'||g_schema||'.'||g_target_country_table);
572   --
573   dbg_time('Update Start');
574   --
575   -- UPDATE -> Rows where PK has stayed the same but other attributes / parents
576   --           have changed
577   --           Results from -> Countries that have had any of these change:
578   --             1) Area changed
579   --             2) Start Date
580   --             3) End Date
581   -- 4546781
582   -- Changed predicates of set select statement where and update where clause.
583   --
584   UPDATE hri_cs_geo_country_ct tbl
585      SET
586    (       geo_area_code
587          , geo_country_code
588          , start_date
589          , end_date
590          , last_change_date
591    ) =
592    (SELECT csc.geo_area_code
593          , csc.geo_country_code
594          , csc.start_date
595          , csc.end_date
596          , csc.last_change_date
597       FROM hri_dbi_cs_geo_country_v csc
598      WHERE csc.geo_country_code       = tbl.geo_country_code
599        AND (   csc.geo_area_code     <> tbl.geo_area_code
600             OR csc.start_date        <> tbl.start_date
601             OR csc.end_date          <> tbl.end_date
602            )
603    )
604    WHERE EXISTS
605          (SELECT 'X'
606             FROM hri_dbi_cs_geo_country_v csc
607            WHERE csc.geo_country_code       = tbl.geo_country_code
608              AND (   csc.geo_area_code     <> tbl.geo_area_code
609                   OR csc.start_date        <> tbl.start_date
610                   OR csc.end_date          <> tbl.end_date
611                  )
612          )
613   ;
614   dbg_time('Update End');
615   --
616   dbg('Update >'||TO_CHAR(sql%rowcount));
617   --
618   -- DELETE -> PKs / Rows that are old
619   --           , i.e. in table but no longer in source view
620   --           Results from -> Country being removed for all hr locations, via:
621   --             1) Location attribution to a country
622   --             2) Location attribution to a region
623   --             3) Region attribution to Country (with at least 1 Location
624   --                 having that Region)
625   --
626   dbg_time('Delete Start');
627   DELETE
628     FROM hri_cs_geo_country_ct tbl
629    WHERE NOT EXISTS
630          (SELECT 'x'
631             FROM hri_dbi_cs_geo_country_v csc
632            WHERE csc.geo_country_code       = tbl.geo_country_code
633          )
634   ;
635   dbg_time('Delete End');
636   --
637   dbg('Delete >'||TO_CHAR(sql%rowcount));
638   --
639   -- INSERT -> PKs / Rows that are new
640   --           , i.e. in source view but not so far in the table
641   --           Results from -> New Countries being brought in via:
642   --             1) Location attributed to country
643   --             2) Location attributed to region (with Country not in list)
644   --             3) Region attributed to Country (with at least 1 Location
645   --                  having that Region)
646   --
647   dbg_time('Insert Start');
648   INSERT
649       INTO hri_cs_geo_country_ct
650          ( geo_area_code
651          , geo_country_code
652          , start_date
653          , end_date
654          , last_change_date
655          )
656     SELECT csc.geo_area_code
657          , csc.geo_country_code
658          , csc.start_date
659          , csc.end_date
660          , csc.last_change_date
661       FROM hri_dbi_cs_geo_country_v csc
662      WHERE NOT EXISTS
663            (SELECT 'x'
664               FROM hri_cs_geo_country_ct tbl
665              WHERE csc.geo_country_code       = tbl.geo_country_code
666            )
667   ;
668   dbg_time('Insert End');
669   --
670   dbg('Insert >'||TO_CHAR(sql%rowcount));
671   --
672   -- @@ Code specific to this view/table below ENDS
673   --
674   dbg('Committing');
675   COMMIT;
676   --
677   dbg('Exiting -> Incremental Refresh Region Structure');
678   --
679 EXCEPTION
680   --
681   WHEN OTHERS THEN
682     --
683     Output('Failure in country structure incremental update process.');
684     output(SQLERRM);
685     --
686     g_msg_sub_group := NVL(g_msg_sub_group, 'INCR_REFRESH_COUNTRY_STRUCT');
687     --
688     ROLLBACK;
689     --
690     RAISE;
691     --
692   --
693 END Incr_Refresh_Country_Struct;
694 -- -----------------------------------------------------------------------------
695 --
696 -- FULL REFRESH PROCEDURES
697 --
698 -- -----------------------------------------------------------------------------
699 -- Procedure to full refresh the hr location structure table
700 -- -----------------------------------------------------------------------------
701 PROCEDURE Full_Refresh_Lochr_Struct IS
702 BEGIN
703   --
704   dbg('Commencing -> Full Refresh LocHR Struct');
705   --
706   dbg(' Table:'||g_schema||'.'||g_target_lochr_table);
707   --
708   dbg('Disabling trigger');
709   run_sql_stmt_noerr('ALTER TRIGGER HRI_CS_GEO_LOCHR_CT_WHO DISABLE');
710   --
711   dbg('Truncating table prior to full refresh');
712   g_sql_stmt := 'TRUNCATE TABLE ' || g_schema || '.'||g_target_lochr_table;
713   dbg_time('Truncate Start');
714   EXECUTE IMMEDIATE(g_sql_stmt);
715   dbg_time('Truncate End');
716   --
717   -- Main Insert
718   -- @@ Code specific to this view/table below
719   -- @@ INTRUCTION TO DEVELOPER:
720   -- @@ 1/ Change the select beloe to select all the columns from your view
721   -- @@ 2/ Change the FROM statement to point at the relevant source view
722   -- (Bug 2950564: Uses APPEND hint to disable MV Log)
723   --
724   dbg_time('Insert Start');
725   INSERT /*+ APPEND */
726   INTO   hri_cs_geo_lochr_ct
727          (area_code
728          ,country_code
729          ,region_code
730          ,city_cid
731          ,location_id
732          ,geo_area_id
733          ,geo_country_id
734          ,geo_region_id
735          ,city_src_town_or_city_txt
736          ,effective_start_date
737          ,effective_end_date
738          ,business_group_id
739          ,last_change_date
740          ,last_update_date
741          ,last_update_login
742          ,last_updated_by
743          ,created_by
744          ,creation_date
745          )
746   SELECT area_code,
747          country_code,
748          region_code,
749          city_cid,
750          location_id,
751          geo_area_id,
752          geo_country_id,
753          geo_region_id,
754          city_src_town_or_city_txt,
755          effective_start_date,
756          effective_end_date,
757          business_group_id,
758          NVL(last_change_date, g_dbi_collection_start_date),
759          g_current_time,
760          g_user_id,
761          g_user_id,
762          g_user_id,
763          g_current_time
764     FROM hri_cs_geo_lochr_v svw
765   ;
766   dbg_time('Insert End');
767   --
768   -- @@Code specific to this view/table below ENDS
769   --
770   COMMIT;
771   --
772   dbg('Re-Enabling Who Trigger');
773   run_sql_stmt_noerr('ALTER TRIGGER HRI_CS_GEO_LOCHR_CT_WHO ENABLE');
774   --
775   dbg_time('Gather Stats Start');
776   fnd_stats.gather_table_stats(g_schema, g_target_lochr_table);
777   dbg_time('Gather Stats End');
778   --
779   dbg('Exiting -> Full Refresh LocHR Struct');
780   --
781 EXCEPTION
782   --
783   WHEN OTHERS THEN
784     --
785     Output('Failure in location structure full refresh process.');
786     output(SQLERRM);
787     --
788     g_msg_sub_group := NVL(g_msg_sub_group, 'FULL_REFRESH_LOCHR_STRUCT');
789     --
790     --   115.15 - 4278978: Require rollbacks for each structure collection
791     ROLLBACK;
792     --
793     RAISE;
794     --
795 END Full_Refresh_Lochr_Struct;
796 -- -----------------------------------------------------------------------------
797 -- Procedure to full refresh the region structure table
798 -- -----------------------------------------------------------------------------
799 PROCEDURE Full_Refresh_Region_Struct
800   IS
801 BEGIN
802   --
803   dbg('Commencing -> Full Refresh Region Struct');
804   --
805   dbg(' Table:'||g_schema||'.'||g_target_region_table);
806   --
807   dbg('Disabling trigger');
808   run_sql_stmt_noerr('ALTER TRIGGER HRI_CS_GEO_REGION_CT_WHO DISABLE');
809   --
810   dbg('Truncating table prior to full refresh');
811   g_sql_stmt := 'TRUNCATE TABLE ' || g_schema || '.'||g_target_region_table;
812   dbg_time('Truncate Start');
813   EXECUTE IMMEDIATE(g_sql_stmt);
814   dbg_time('Truncate End');
815   --
816   dbg_time('Insert Start');
817   INSERT /*+APPEND */
818     INTO hri_cs_geo_region_ct
819          ( geo_area_code
820          , geo_country_code
821          , geo_region_code
822          , geo_region_sk_pk
823          , start_date
824          , end_date
825          , LAST_CHANGE_DATE
826          , CREATION_DATE
827          , CREATED_BY
828          , LAST_UPDATE_DATE
829          , LAST_UPDATED_BY
830          , LAST_UPDATE_LOGIN
831          )
832     SELECT csr.geo_area_code                      geo_area_code
833          , csr.geo_country_code                   geo_country_code
834          , csr.geo_region_code                    geo_region_code
835          , csr.geo_region_sk_pk                   geo_region_sk_pk
836          , csr.start_date                         start_date
837          , csr.end_date                           end_date
838          , csr.last_change_date                   last_change_date
839          , g_current_time                         CREATION_DATE
840          , g_user_id                              CREATED_BY
841          , g_current_time                         LAST_UPDADTE_DATE
842          , g_user_id                              LAST_UPDATE_BY
843          , g_user_id                              LAST_UPDATE_LOGIN
844       FROM hri_dbi_cs_geo_region_v                csr
845   ;
846   dbg_time('Insert End');
847   --
848   -- @@Code specific to this view/table below ENDS
849   --
850   dbg('Commiting');
851   COMMIT;
852   --
853   dbg('Re-Enabling Who Trigger');
854   run_sql_stmt_noerr('ALTER TRIGGER HRI_CS_GEO_REGION_CT_WHO ENABLE');
855   --
856   dbg_time('Gather Stats Start');
857   fnd_stats.gather_table_stats(g_schema, g_target_region_table);
858   dbg_time('Gather Stats End');
859   --
860   dbg('Exiting -> Full Refresh Region Struct');
861   --
862 EXCEPTION
863   --
864   WHEN OTHERS THEN
865     --
866     Output('Failure in region structure full refresh process.');
867     output(SQLERRM);
868     --
869     g_msg_sub_group := NVL(g_msg_sub_group, 'FULL_REFRESH_REGION_STRUCT');
870     --
871     ROLLBACK;
872     --
873     RAISE;
874   --
875 END Full_Refresh_Region_Struct;
876 -- -----------------------------------------------------------------------------
877 -- Procedure to full refresh the country structure table
878 -- -----------------------------------------------------------------------------
879 PROCEDURE Full_Refresh_Country_Struct
880   IS
881 BEGIN
882   --
883   dbg('Commencing -> Full Refresh Region Struct');
884   --
885   dbg(' Table : '||g_schema||'.'||g_target_country_table);
886   --
887   dbg('Disabling trigger');
888   run_sql_stmt_noerr('ALTER TRIGGER HRI_CS_GEO_COUNTRY_CT_WHO DISABLE');
889   --
890   dbg('Truncating table prior to full refresh');
891   g_sql_stmt := 'TRUNCATE TABLE ' || g_schema || '.'||g_target_country_table;
892   dbg_time('Truncate Start');
893   EXECUTE IMMEDIATE(g_sql_stmt);
894   dbg_time('Truncate End');
895   --
896   dbg_time('Insert Start');
897   INSERT /*+APPEND */
898     INTO hri_cs_geo_country_ct
899          ( geo_area_code
900          , geo_country_code
901          , start_date
902          , end_date
903          , LAST_CHANGE_DATE
904          , CREATION_DATE
905          , CREATED_BY
906          , LAST_UPDATE_DATE
907          , LAST_UPDATED_BY
908          , LAST_UPDATE_LOGIN
909          )
910     SELECT csc.geo_area_code                        geo_area_code
911          , csc.geo_country_code                     geo_country_code
912          , csc.start_date                           start_date
913          , csc.end_date                             end_date
914          , csc.last_change_date                     last_change_date
915          , g_current_time                           CREATION_DATE
916          , g_user_id                                CREATED_BY
917          , g_current_time                           LAST_UPDATE_DATE
918          , g_user_id                                LAST_UPDATED_BY
919          , g_user_id                                LAST_UPDATE_LOGIN
920       FROM hri_dbi_cs_geo_country_v                 csc
921   ;
922   dbg_time('Insert End');
923   --
924   -- @@Code specific to this view/table below ENDS
925   --
926   dbg('Commiting');
927   COMMIT;
928   --
929   -- Re-enable the WHO trigger
930   --
931   dbg('Re-Enabling Who Trigger');
932   run_sql_stmt_noerr('ALTER TRIGGER HRI_CS_GEO_COUNTRY_CT_WHO ENABLE');
933   --
934   dbg_time('Gather Stats Start');
935   fnd_stats.gather_table_stats(g_schema, g_target_country_table);
936   dbg_time('Gather Stats End');
937   --
938   dbg('Exiting -> Full Refresh Country Struct');
939   --
940 EXCEPTION
941   --
942   WHEN OTHERS THEN
943     --
944     Output('Failure in country structure full refresh process.');
945     output(SQLERRM);
946     --
947     g_msg_sub_group := NVL(g_msg_sub_group, 'FULL_REFRESH_COUNTRY_STRUCT');
948     --
949     ROLLBACK;
950     --
951     RAISE;
952   --
953 END Full_Refresh_Country_Struct;
954 --
955 -- -----------------------------------------------------------------------------
956 -- Incremental Refresh
957 --   Controller procedure for incremental refresh of all objects
958 --
959 --   115.15 - 4278978
960 --   Added as new structure require collecting
961 --   Note: Exceptions are handled in individual procedures
962 --   Renamed procedure to more standard name
963 --    FROM: Incremental_Update
964 --      TO: Incr_Refresh
965 -- -----------------------------------------------------------------------------
966 PROCEDURE Incr_Refresh IS
967   --
968 BEGIN
969   --
970   output('Commencing Location Incremental                 : ' ||
971          to_char(sysdate,'HH24:MI:SS'));
972   Incr_Refresh_Lochr_Struct;
973   output('Location incremental complete, commencing Region: '||
974          to_char(sysdate,'HH24:MI:SS'));
975   Incr_Refresh_Region_Struct;
976   output('Region incremental complete, commencing Country : '||
977          to_char(sysdate,'HH24:MI:SS'));
978   Incr_Refresh_Country_Struct;
979   output('Country incremental complete                    : '||
980          to_char(sysdate,'HH24:MI:SS'));
981   --
982 END Incr_Refresh;
983 --
984 -- -----------------------------------------------------------------------------
985 -- Full Refresh
986 --   Controller procedure for full refresh of all objects
987 
988 --   115.15 - 4278978
989 --   Added as new structure require collecting
990 --   Note: Exceptions are handled in individual procedures
991 -- -----------------------------------------------------------------------------
992 PROCEDURE Full_Refresh
993   IS
994   --
995 BEGIN
996   --
997   output('Commencing Location Full                        : ' ||
998          to_char(sysdate,'HH24:MI:SS'));
999   Full_Refresh_Lochr_Struct;
1000   output('Location Full complete, commencing Region       : '||
1001          to_char(sysdate,'HH24:MI:SS'));
1002   Full_Refresh_Region_Struct;
1003   output('Region Full complete, commencing Country        : '||
1004          to_char(sysdate,'HH24:MI:SS'));
1005   Full_Refresh_Country_Struct;
1006   output('Country Full complete                           : '||
1007          to_char(sysdate,'HH24:MI:SS'));
1008   --
1009 END Full_Refresh;
1010 --
1011 -- -------------------------------------------------------------------------
1012 -- Checks what mode you are running in, and if g_full_refresh =
1013 -- g_is_full_refresh calls
1014 -- Full_Refresh procedure, otherwise Incremental_Update is called.
1015 -- -------------------------------------------------------------------------
1016 --
1017 PROCEDURE Collect IS
1018   --
1019 BEGIN
1020   --
1021   dbg('Commencing -> Collect');
1022   --
1023   dbg('Setup Globals');
1024   g_user_id      := fnd_global.user_id;
1025   dbg(' USER_ID : '|| to_char(g_user_id));
1026   g_current_time := SYSDATE;
1027   dbg(' Collection Date and Time : '||to_char(g_current_time));
1028   --
1029   -- If in full refresh mode chnage the dates so that the collection history
1030   -- is correctly maintained.
1031   --
1032   IF g_full_refresh = g_is_full_refresh THEN
1033     --
1034     g_start_date   := hr_general.start_of_time;
1035     g_end_date     := SYSDATE;
1036     --
1037     Full_Refresh;
1038     --
1039   ELSE
1040     --
1041     -- If the passed in date range is NULL default it.
1042     --
1043     IF g_start_date IS NULL OR
1044        g_end_date   IS NULL THEN
1045       --
1046       dbg('Before updating globals Start Date = '
1047           || g_start_date||', End Date = '||g_end_date);
1048       --
1049       g_start_date := fnd_date.displaydt_to_date
1050                               (hri_bpl_conc_log.get_last_collect_to_date
1051                                       (g_cncrnt_prgrm_shrtnm
1052                                       ,g_target_lochr_table
1053                                       )
1054                               );
1055       --
1056       g_end_date := SYSDATE;
1057       --
1058       dbg('After updating globals Start Date = '
1059           || g_start_date||', End Date = '||g_end_date);
1060       --
1061     END IF;
1062     --
1063     Incr_Refresh;
1064     --
1065   END IF;
1066   --
1067   dbg('Exiting -> Collect');
1068   --
1069   -- Bug 4105868: Collection Diagnostics
1070   --
1071 EXCEPTION
1072   --
1073   WHEN OTHERS THEN
1074     --
1075     g_msg_sub_group := NVL(g_msg_sub_group, 'COLLECT');
1076     --
1077     RAISE;
1078     --
1079 END Collect;
1080 -- -----------------------------------------------------------------------------
1081 -- Main entry point to load the table.
1082 -- -----------------------------------------------------------------------------
1083 --
1084 PROCEDURE Load(p_chunk_size    IN NUMBER
1085               ,p_start_date    IN VARCHAR2
1086               ,p_end_date      IN VARCHAR2
1087               ,p_full_refresh  IN VARCHAR2) IS
1088   --
1089   -- Variables required for table truncation.
1090   --
1091   l_dummy1        VARCHAR2(2000);
1092   l_dummy2        VARCHAR2(2000);
1093   --
1094 BEGIN
1095   --
1096   dbg('Commencing -> Load');
1097   --
1098   dbg_time('PL/SQL Start');
1099   --
1100   -- Set globals
1101   --
1102   g_start_date := to_date(p_start_date, 'YYYY/MM/DD HH24:MI:SS');
1103   g_end_date   := to_date(p_end_date,   'YYYY/MM/DD HH24:MI:SS');
1104   --
1105   IF p_full_refresh IS NULL THEN
1106     --
1107     g_full_refresh := g_not_full_refresh;
1108     --
1109   ELSE
1110     --
1111     g_full_refresh := p_full_refresh;
1112     --
1113   END IF;
1114   --
1115   -- If the target table is empty default to full refresh.
1116   --
1117   IF Target_table_is_Empty THEN
1118     --
1119     dbg('Target table '||g_target_lochr_table||
1120            ' is empty, so doing a full refresh.');
1121     --
1122     g_full_refresh := g_is_full_refresh;
1123     --
1124   END IF;
1125   --
1126   -- Find the schema we are running in.
1127   --
1128   IF NOT fnd_installation.get_app_info('HRI',l_dummy1, l_dummy2, g_schema) THEN
1129     --
1130     -- Could not find the schema raising exception.
1131     --
1132     dbg('Could not find schema to run in.');
1133     --
1134     RAISE NO_DATA_FOUND;
1135     --
1136   END IF;
1137   --
1138   -- Update information about collection
1139   --
1140   hri_bpl_conc_log.record_process_start(g_cncrnt_prgrm_shrtnm);
1141   --
1142   collect;
1143   --
1144   dbg_time('Completed table changes');
1145   /*
1146   115.15 4278978
1147   Commenting out gather table stats and moving to hr location structure collection
1148   procedure in order to be prepared for parent structure collections
1149   --
1150   -- Gather index stats
1151   --
1152   dbg('gather table stats Schema = '
1153       ||g_schema||', Table = '||g_target_lochr_table);
1154   --
1155   fnd_stats.gather_table_stats(g_schema, g_target_lochr_table);
1156   --
1157   dbg('Gathered stats:   '  ||
1158          to_char(sysdate,'HH24:MI:SS'));
1159   /**/
1160   --
1161   -- Bug 4105868: Collection Diagnostic Call
1162   --
1163   hri_bpl_conc_log.log_process_end(
1164         p_status         => TRUE,
1165         p_period_from    => TRUNC(g_start_date),
1166         p_period_to      => TRUNC(g_end_date),
1167         p_attribute1     => p_full_refresh,
1168         p_attribute2     => p_chunk_size);
1169   --
1170   dbg_time('PL/SQL End');
1171   --
1172   dbg('Exiting -> Load');
1173   --
1174 EXCEPTION
1175   --
1176   WHEN OTHERS THEN
1177     --
1178     -- 115.15 4278978
1179     -- Commentin out rollback as multiple structure are collected
1180     -- changing to localised exception handling and Rollbacks
1181     --ROLLBACK;
1182     --
1183     -- Insert the error into the log table
1184     -- Bug 4105868: Collection Diagnostic Call
1185     --
1186     g_msg_sub_group := nvl(g_msg_sub_group, 'LOAD');
1187     --
1188     hri_bpl_conc_log.log_process_info
1189             (p_package_name      => 'HRI_OPL_GEO_LOCHR'
1190             ,p_msg_type          => 'ERROR'
1191             ,p_msg_group         => 'GEOGRAPHY'
1192             ,p_msg_sub_group     => g_msg_sub_group
1193             ,p_sql_err_code      => SQLCODE
1194             ,p_note              => SQLERRM);
1195     --
1196     -- Insert Program failure details into the log tables
1197     -- Bug 4105868: Collection Diagnostic Call
1198     --
1199     hri_bpl_conc_log.log_process_end
1200             (p_status         => FALSE
1201             ,p_period_from    => TRUNC(g_start_date)
1202             ,p_period_to      => TRUNC(g_end_date)
1203             ,p_attribute1     => p_full_refresh
1204             ,p_attribute2     => p_chunk_size
1205             );
1206     --
1207     RAISE;
1208     --
1209   --
1210 END Load;
1211 --
1212 -- -----------------------------------------------------------------------------
1213 -- Entry point to be called from the concurrent manager
1214 -- -----------------------------------------------------------------------------
1215 --
1216 PROCEDURE Load(errbuf          OUT NOCOPY VARCHAR2
1217               ,retcode         OUT NOCOPY VARCHAR2
1218               ,p_chunk_size    IN NUMBER
1219               ,p_start_date    IN VARCHAR2
1220               ,p_end_date      IN VARCHAR2
1221               ,p_full_refresh  IN VARCHAR2
1222               ) IS
1223 --
1224 BEGIN
1225   --
1226   load(p_chunk_size   => p_chunk_size
1227       ,p_start_date   => p_start_date
1228       ,p_end_date     => p_end_date
1229       ,p_full_refresh => p_full_refresh
1230       );
1231   --
1232 EXCEPTION
1233   --
1234   WHEN OTHERS THEN
1235     --
1236     errbuf  := SQLERRM;
1237     retcode := SQLCODE;
1238     --
1239   --
1240 END load;
1241 
1242 PROCEDURE Load(errbuf          OUT NOCOPY VARCHAR2
1243               ,retcode         OUT NOCOPY VARCHAR2) IS
1244 
1245   l_start_date             VARCHAR2(80);
1246   l_end_date               VARCHAR2(80);
1247   l_full_refresh           VARCHAR2(10);
1248 
1249 BEGIN
1250 
1251   l_full_refresh := hri_oltp_conc_param.get_parameter_value
1252                      (p_parameter_name     => 'FULL_REFRESH',
1253                       p_process_table_name => 'HRI_CS_GEO_LOCHR_CT');
1254   IF (l_full_refresh = 'Y') THEN
1255     l_start_date := hri_oltp_conc_param.get_parameter_value
1256                      (p_parameter_name     => 'FULL_REFRESH_FROM_DATE',
1257                       p_process_table_name => 'HRI_CS_GEO_LOCHR_CT');
1258   ELSE
1259     -- Bug 4704157 - converted displaydt to canonical
1260     l_start_date := fnd_date.date_to_canonical
1261                      (fnd_date.displaydt_to_date
1262                        (hri_bpl_conc_log.get_last_collect_to_date
1263                          ('HRI_OPL_GEO_LOCHR','HRI_CS_GEO_LOCHR_CT')));
1264   END IF;
1265 
1266   hri_bpl_conc_log.dbg('Full refresh:   ' || l_full_refresh);
1267   hri_bpl_conc_log.dbg('Collect from:   ' || l_start_date);
1268 
1269   --
1270   load(p_chunk_size   => 1500
1271       ,p_start_date   => l_start_date
1272       ,p_end_date     => trunc(sysdate)
1273       ,p_full_refresh => l_full_refresh
1274       );
1275   --
1276 EXCEPTION
1277   --
1278   WHEN OTHERS THEN
1279     --
1280     errbuf  := SQLERRM;
1281     retcode := SQLCODE;
1282     --
1283   --
1284 END load;
1285 --
1286 END HRI_OPL_GEO_LOCHR;