DBA Data[Home] [Help]

PACKAGE BODY: APPS.OPI_DBI_RES_PKG

Source


1 PACKAGE BODY OPI_DBI_RES_PKG AS
2 /* $Header: OPIDRESB.pls 120.26 2007/03/12 06:57:25 hyadaval ship $ */
3 
4 /*========================================
5     Package Level Variables
6 =========================================*/
7 -- Standard who columns
8 g_user_id                   NUMBER;
9 g_login_id                  NUMBER;
10 g_program_id                NUMBER;
11 g_program_login_id          NUMBER;
12 g_program_application_id    NUMBER;
13 g_request_id                NUMBER;
14 
15 -- DBI global start date
16 g_global_start_date         DATE;
17 
18 -- Conversion rate related variables
19 g_global_currency_code      VARCHAR2(10);
20 g_global_rate_type          VARCHAR2(15);
21 g_secondary_currency_code   VARCHAR2(10);
22 g_secondary_rate_type       VARCHAR2 (15);
23 
24 g_hr_uom                    sy_uoms_mst_v.um_code%TYPE;
25 
26 
27 /*========================================
28     Package Level Constants
29 =========================================*/
30 
31 g_ok CONSTANT NUMBER(1)  := 0;
32 g_warning CONSTANT NUMBER(1)  := 1;
33 g_error CONSTANT NUMBER(1)  := -1;
34 
35 OPI_SOURCE CONSTANT NUMBER := 1;
36 OPM_SOURCE              CONSTANT NUMBER := 2;
37 PRE_R12_OPM_SOURCE      CONSTANT NUMBER := 3;
38 
39 
40 --ETL ID for OPI_DBI_RUN_LOG_CURR
41 
42 -- Actual Resource Usage
43 ACTUAL_RES_ETL CONSTANT NUMBER :=
44     opi_dbi_common_mod_init_pkg.ACTUAL_RES_ETL;
45 
46 -- Resource Availability
47 RESOURCE_VAR_ETL CONSTANT NUMBER :=
48     opi_dbi_common_mod_init_pkg.RESOURCE_VAR_ETL;
49 
50 -- start date of euro currency.
51 G_EURO_START_DATE CONSTANT DATE := to_date('01/01/1999','DD/MM/YYYY');
52 
53 
54 -- Marker for secondary conv. rate if the primary and secondary curr codes
55 -- and rate types are identical. Can't be -1, -2, -3 since the FII APIs
56 -- return those values.
57 C_PRI_SEC_CURR_SAME_MARKER CONSTANT NUMBER := -9999;
58 
59 -- GL API returns -3 if EURO rate missing on 01-JAN-1999
60 C_EURO_MISSING_AT_START CONSTANT NUMBER := -3;
61 
62 
63 /*===============================================================
64     This procedure gather statistics of a table.
65 
66     Parameters:
67     - p_table_name: table name
68 ================================================================*/
69 
70 PROCEDURE gather_stats (p_table_name    VARCHAR2) IS
71 
72     l_table_owner  VARCHAR2(32);
73 
74 BEGIN
75     bis_collection_utilities.put_line('Enter gather_stats() ' ||
76                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
77 
78     -- Find owner of the table passed to procedure
79 
80     SELECT  table_owner
81     INTO    l_table_owner
82     FROM    user_synonyms
83     WHERE   synonym_name = p_table_name;
84 
85     --   Gather table statistics these stats will be used by CBO
86     --   for query optimization.
87 
88     FND_STATS.GATHER_TABLE_STATS(l_table_owner,P_TABLE_NAME,
89                         PERCENT=>10,DEGREE=>4,CASCADE=>TRUE);
90 
91     bis_collection_utilities.put_line('Exit gather_stats() ' ||
92                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
93 END gather_stats;
94 
95 /*===============================================================
96     This procedure sets up global parameters, such as the global
97     start date, globla/secondary currencies, WHO column variables.
98 
99     Parameters:
100     - errbuf:   error buffer
101     - retcode:  return code
102 =================================================================*/
103 
104 PROCEDURE check_setup_globals ( errbuf  IN OUT NOCOPY VARCHAR2,
105                                 retcode IN OUT NOCOPY VARCHAR2)
106 IS
107 
108     l_list dbms_sql.varchar2_table;
109 
110     l_from_date  DATE;
111     l_to_date    DATE;
112     l_missing_day_flag BOOLEAN;
113     l_err_num    NUMBER;
114     l_err_msg    VARCHAR2(255);
115     l_min_miss_date DATE;
116      l_max_miss_date DATE;
117 
118 BEGIN
119 
120     bis_collection_utilities.put_line('Enter check_setup_globals() ' ||
121                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
122 
123     -- initialization block
124     l_missing_day_flag := false;
125     retcode   := g_ok;
126 
127     -- package level variables
128     g_hr_uom := fnd_profile.value( 'BOM:HOUR_UOM_CODE');
129 
130     g_user_id := nvl(fnd_global.user_id, -1);
131     g_login_id := nvl(fnd_global.login_id, -1);
132     g_program_id := nvl (fnd_global.conc_program_id, -1);
133     g_program_login_id := nvl (fnd_global.conc_login_id, -1);
134     g_program_application_id := nvl (fnd_global.prog_appl_id,  -1);
135     g_request_id := nvl (fnd_global.conc_request_id, -1);
136 
137 
138     IF (g_global_rate_type IS NULL) THEN
139     --{
140        g_global_rate_type := bis_common_parameters.get_rate_type;
141     --}
142     END IF;
143 
144     l_list(1) := 'BIS_PRIMARY_CURRENCY_CODE';
145     l_list(2) := 'BIS_GLOBAL_START_DATE';
146     l_list(3) := 'BIS_PRIMARY_RATE_TYPE';
147 
148     IF (bis_common_parameters.check_global_parameters(l_list)) THEN
149     --{
150         -- GSD -- already checked if it is set up
151         g_global_start_date := bis_common_parameters.get_global_start_date;
152 
153         -- Global currency codes -- already checked if primary is set up
154         g_global_currency_code := bis_common_parameters.get_currency_code;
155         g_secondary_currency_code :=
156                 bis_common_parameters.get_secondary_currency_code;
157 
158         -- Global rate types -- already checked if primary is set up
159         g_global_rate_type := bis_common_parameters.get_rate_type;
160         g_secondary_rate_type := bis_common_parameters.get_secondary_rate_type;
161 
162         -- check that either both the secondary rate type and secondary
163         -- rate are null, or that neither are null.
164         IF (   (g_secondary_currency_code IS NULL AND
165                 g_secondary_rate_type IS NOT NULL)
166             OR (g_secondary_currency_code IS NOT NULL AND
167                  g_secondary_rate_type IS NULL) ) THEN
168         --{
169             retcode := g_error;
170             errbuf := 'Please check log file for details.';
171             bis_collection_utilities.put_line ('The global secondary currency code setup is incorrect.' ||
172                                   'The secondary currency code cannot be null when the ' ||
173                                   'secondary rate type is defined and vice versa.');
174         --}
175         END IF;
176 
177         -- check_missing_dates in time dimension
178         select sysdate into l_to_date from dual;
179         fii_time_api.check_missing_date (g_global_start_date,
180                                          l_to_date,
181                                          l_missing_day_flag,
182                                          l_min_miss_date, l_max_miss_date);
183 
184         IF l_missing_day_flag THEN
185         --{
186             retcode := g_error;
187             errbuf  := 'Please check log file for details. ';
188             bis_collection_utilities.put_line( 'There are missing date in Time Dimension.');
189 
190             bis_collection_utilities.put_line ( 'The range is from ' || l_min_miss_date
191                                     ||' to ' || l_max_miss_date );
192         --}
193         END IF;
194     --}
195     ELSE
196     --{
197         retcode := g_error;
198         errbuf  := 'Please check log file for details. ';
199         bis_collection_utilities.put_line('Global Parameters are not setup.');
200 
201         bis_collection_utilities.put_line('Please check that the profile options: BIS_PRIMARY_CURRENCY_CODE and BIS_GLOBAL_START_DATE are setup.');
202     --}
203     END  IF;
204 
205     bis_collection_utilities.put_line('Exit check_setup_globals() ' ||
206                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
207 
208 EXCEPTION
209     WHEN OTHERS THEN
210     --{
211         retcode := SQLCODE;
212         errbuf :=   'ERROR in OPI_DBI_RES_PKG.CHECK_SETUP_GLOBALS ' ||
213                     substr(SQLERRM, 1,200);
214          bis_collection_utilities.put_line('Error Number: ' ||  retcode);
215         bis_collection_utilities.put_line('Error Message: ' || errbuf);
216     --}
217 END check_setup_globals;
218 
219 
220 /*========================================================================
221  get_res_conversion_rate
222 
223 
224     Compute all the conversion rates for all distinct organization,
225     transaction date pairs in the staging table. The date in the fact
226     table is already without a timestamp i.e. trunc'ed.
227 
228     There are two conversion rates to be computed:
229     1. Primary global
230     2. Secondary global (if set up)
231 
232     The conversion rate work table was truncated during
233     the initialization phase.
234 
235     Get the currency conversion rates based on the data in
236     OPI_DBI_RES_ACTUAL_STG using the fii_currency.get_global_rate_primary
237     API for the primary global currency and
238     fii_currency.get_global_rate_secondary for the secondary global currency.
239     The primary currency API:
240     1. finds the conversion rate if one exists.
241     2. returns -1 if there is no conversion rate on that date.
242     3. returns -2 if the currency code is not found.
243     4. returns -3 if the transaction_date is prior to 01-JAN-1999,
244        the functional currency code is EUR and there is no EUR to USD
245        conversion rate defined on 01-JAN-1999.
246 
247     The secondary currency API:
248     1. Finds the global secondary currency rate if one exists.
249     2. Returns a rate of 1 if the secondary currency has not been set up.
250     3. Returns -1, -2, -3 in the same way as the primary currency code API.
251 
252     If the global and secondary currency codes and rate types are identical,
253     do not call the secondary currency API. Instead update the secondary
254     rates from the primary.
255 
256     If the secondary currency has not been set up, set the conversion rate
257     to null.
258 
259     If any primary conversion rates are missing, throw an exception.
260     If any secondary currency rates are missing (after the secondary
261     currency has been set up) throw an exception.
262 
263      In the previous version, there were no commits in this function.
264     However, there was a commit right after this function's call
265     everywhere. So it is safe to change the insert to an insert+append
266     and commit inside the function.
267 
268     Date            Author              Action
269     08/26/2004      Dinkar Gupta        Modified to provide secondary
270                                         currency support.
271 ===============================================================================*/
272 
273 PROCEDURE get_res_conversion_rate ( errbuf  IN OUT NOCOPY VARCHAR2,
274                                     retcode IN OUT NOCOPY VARCHAR2 )
275 IS
276 
277     -- Cursor to see if any rates are missing. See below for details
278     CURSOR invalid_rates_exist_csr IS
279         SELECT  1
280         FROM    opi_dbi_res_conv_rates
281         WHERE   (nvl (conversion_rate, -999) < 0
282                  OR nvl (sec_conversion_rate, 999) < 0)
283         AND     rownum < 2;
284 
285     invalid_rates_exist_rec invalid_rates_exist_csr%ROWTYPE;
286 
287 
288     -- Set up a cursor to get all the invalid rates.
289     -- By the logic of the fii_currency.get_global_rate_primary
290     -- and fii_currency.get_global_rate_secondary APIs, the returned value
291     -- is -ve if no rate exists:
292     -- -1 for dates with no rate.
293     -- -2 for unrecognized conversion rates.
294     -- -3 for missing EUR to USD rates on 01-JAN-1999 when the
295     --    transaction_date is prior to 01-JAN-1999 (when the EUR
296     --    officially went into circulation).
297     --
298     -- However, with the secondary currency, the null rate means it
299     -- has not been setup and should therefore not be reported as an
300     -- error.
301     --
302     -- Also, cross check with the org-date pairs in the staging table,
303     -- in case some orgs never had a functional currency code defined.
304     CURSOR get_missing_rates_c (p_pri_sec_curr_same NUMBER,
305                                 p_global_currency_code VARCHAR2,
306                                 p_global_rate_type VARCHAR2,
307                                 p_secondary_currency_code VARCHAR2,
308                                 p_secondary_rate_type VARCHAR2) IS
309      SELECT  DISTINCT
310             report_order,
311             curr_code,
312             rate_type,
313             transaction_date,
314             func_currency_code
315     FROM (
316            SELECT /*+ parallel (to_conv) parallel (conv) parallel (mp) */
317                     DISTINCT
318                     p_global_currency_code  curr_code,
319                     p_global_rate_type  rate_type,
320                     1 report_order, -- ordering global currency first
321                     mp.organization_code,
322                     decode (conv.conversion_rate,
323                             C_EURO_MISSING_AT_START, G_EURO_START_DATE,
324                             conv.transaction_date) transaction_date,
325                     conv.f_currency_code func_currency_code
326             FROM    opi_dbi_res_conv_rates conv,
327                     mtl_parameters mp,
328                     (
329                     SELECT /*+ parallel (opi_dbi_res_actual_stg) */
330                             DISTINCT
331                             organization_id,
332                             transaction_date
333                     FROM    opi_dbi_res_actual_stg
334                     UNION
335                     SELECT /*+ parallel (opi_dbi_res_avail_stg) */
336                             DISTINCT
337                             organization_id,
338                             transaction_date
339                     FROM    opi_dbi_res_avail_stg)  to_conv
340             WHERE   nvl (conv.conversion_rate, -999) < 0 -- null is not fine
341             AND     mp.organization_id = to_conv.organization_id
342             AND     conv.transaction_date (+) = to_conv.transaction_date
343             AND     conv.organization_id (+) = to_conv.organization_id
344             UNION ALL
345             SELECT /*+ parallel (to_conv) parallel (conv) parallel (mp) */
346                     DISTINCT
347                     p_secondary_currency_code curr_code,
348                     p_secondary_rate_type rate_type,
349                     decode (p_pri_sec_curr_same,
350                             1, 1,
351                             2) report_order, --ordering secondary currency next
352                     mp.organization_code,
353                     decode (conv.sec_conversion_rate,
354                             C_EURO_MISSING_AT_START, G_EURO_START_DATE,
355                             conv.transaction_date) transaction_date_date,
356                     conv.f_currency_code func_currency_code
357              FROM    opi_dbi_res_conv_rates conv,
358                     mtl_parameters mp,
359                     (
360                     SELECT /*+ parallel (opi_dbi_res_actual_stg) */
361                             DISTINCT
362                             organization_id,
363                             transaction_date
364                     FROM    opi_dbi_res_actual_stg
365                     UNION
366                     SELECT /*+ parallel (opi_dbi_res_avail_stg) */
367                             DISTINCT
368                             organization_id,
369                             transaction_date
370                     FROM    opi_dbi_res_avail_stg)  to_conv
371             WHERE   nvl (conv.sec_conversion_rate, 999) < 0 -- null is fine
372             AND     mp.organization_id = to_conv.organization_id
373             AND     conv.transaction_date (+) = to_conv.transaction_date
374             AND     conv.organization_id (+) = to_conv.organization_id)
375      ORDER BY
376             report_order ASC,
377             transaction_date,
378             func_currency_code;
379 
380 
381     -- mark location in procedure
382     l_stmt_num NUMBER;
383 
384     -- Flag to check if the primary and secondary currencies are the same
385     l_pri_sec_curr_same NUMBER;
386 
387     no_currency_rate_flag NUMBER;
388 
389 
390 BEGIN
391 
392 
393     bis_collection_utilities.put_line('Enter get_res_conversion_rate() ' ||
394                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
395 
396     -- initialization block
397     l_pri_sec_curr_same := 0;
398     no_currency_rate_flag := 0;
399     retcode := g_ok;
400 
401     l_stmt_num := 10;
402     -- check if the primary and secondary currencies and rate types are same
403     IF (g_global_currency_code = nvl (g_secondary_currency_code, '---') AND
404         g_global_rate_type = nvl (g_secondary_rate_type, '---') ) THEN
405     --{
406         l_pri_sec_curr_same := 1;
407     --}
408     END IF;
409 
410    l_stmt_num := 10;
411     -- Use the fii_currency.get_global_rate_primary function to get the
412     -- conversion rate given a currency code and a date.
413     -- The function returns:
414     -- 1 for currency code of 'USD' which is the global currency
415     -- -1 for dates for which there is no currency conversion rate
416     -- -2 for unrecognized currency conversion rates
417     -- -3 for missing EUR to USD rates on 01-JAN-1999 when the
418     --    transaction_date is prior to 01-JAN-1999 (when the EUR
419     --    officially went into circulation).
420 
421     -- Use the fii_currency.get_global_rate_secondary to get the secondary
422     -- global rate. If the secondary currency has not been set up,
423     -- make the rate null. If the secondary currency/rate types are the
424     -- same as the primary, don't call the API but rather use an update
425     -- statement followed by the insert.
426 
427     -- By selecting distinct org and currency code from the gl_set_of_books
428     -- and hr_organization_information, take care of duplicate codes.
429     INSERT /*+ append parallel(rates) */
430     INTO    opi_dbi_res_conv_rates rates (
431             organization_id,
432             f_currency_code,
433             transaction_date,
434             conversion_rate,
435             sec_conversion_rate)
436     SELECT /*+ parallel (to_conv) parallel (curr_codes) */
437             to_conv.organization_id,
438             curr_codes.currency_code,
439             to_conv.transaction_date,
440             decode (curr_codes.currency_code,
441                     g_global_currency_code, 1,
442                     fii_currency.get_global_rate_primary (
443                                      curr_codes.currency_code,
444                                     to_conv.transaction_date) ),
445             decode (g_secondary_currency_code,
446                     NULL, NULL,
447                     curr_codes.currency_code, 1,
448                     decode (l_pri_sec_curr_same,
449                             1, C_PRI_SEC_CURR_SAME_MARKER,
450                             fii_currency.get_global_rate_secondary (
451                                 curr_codes.currency_code,
452                                 to_conv.transaction_date)))
453     FROM
454             (SELECT /*+ parallel (opi_dbi_res_actual_stg) */
455                     DISTINCT
456                     organization_id,
457                     trunc (transaction_date) transaction_date
458             FROM    opi_dbi_res_actual_stg
459             UNION
460             SELECT /*+ parallel (opi_dbi_res_avail_stg) */
461                     DISTINCT
462                     organization_id,
463                     trunc (transaction_date) transaction_date
464             FROM    opi_dbi_res_avail_stg)     to_conv,
465             (SELECT /*+ leading (hoi) full (hoi) use_hash (gsob)
466                     parallel (hoi) parallel (gsob)*/
467                     DISTINCT
468                     hoi.organization_id,
469                     gsob.currency_code
470             FROM    hr_organization_information hoi,
471                     gl_sets_of_books gsob
472             WHERE   hoi.org_information_context  = 'Accounting Information'
473             AND     hoi.org_information1  = to_char(gsob.set_of_books_id)) curr_codes
474     WHERE   curr_codes.organization_id  = to_conv.organization_id;
475 
476 
477 
478     --Introduced commit because of append parallel in the insert stmt above.
479     commit;
480 
481     l_stmt_num := 40;
482     -- if the primary and secondary currency codes are the same, then
483     -- update the secondary with the primary
484     IF (l_pri_sec_curr_same = 1) THEN
485     --{
486         UPDATE /*+ parallel (opi_dbi_res_conv_rates) */
487         opi_dbi_res_conv_rates
488         SET sec_conversion_rate = conversion_rate;
489 
490         -- safe to commit, as before
491         commit;
492     --}
493     END IF;
494 
495      -- report missing rate
496     l_stmt_num := 50;
497 
498     OPEN invalid_rates_exist_csr;
499     FETCH invalid_rates_exist_csr INTO invalid_rates_exist_rec;
500     IF (invalid_rates_exist_csr%FOUND) THEN
501     --{
502         -- there are missing rates - prepare to report them.
503         no_currency_rate_flag := 1;
504         BIS_COLLECTION_UTILITIES.writeMissingRateHeader;
505 
506         l_stmt_num := 60;
507         FOR get_missing_rates_rec IN get_missing_rates_c (
508                                             l_pri_sec_curr_same,
509                                             g_global_currency_code,
510                                             g_global_rate_type,
511                                             g_secondary_currency_code,
512                                             g_secondary_rate_type)
513         LOOP
514 
515             BIS_COLLECTION_UTILITIES.writemissingrate (
516                 get_missing_rates_rec.rate_type,
517                 get_missing_rates_rec.func_currency_code,
518                 get_missing_rates_rec.curr_code,
519                 get_missing_rates_rec.transaction_date);
520 
521         END LOOP;
522     --}
523     END IF;
524     CLOSE invalid_rates_exist_csr;
525 
526 
527     l_stmt_num := 70; /* check no_currency_rate_flag  */
528     IF (no_currency_rate_flag = 1) THEN /* missing rate found */
529     --{
530         bis_collection_utilities.put_line('ERROR: Please setup conversion rate for all missing rates reported');
531 
532         retcode := g_error;
533     --}
534     END IF;
535 
536     bis_collection_utilities.put_line('Exit get_res_conversion_rate() ' ||
537                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
538     return;
539 
540 EXCEPTION
541     WHEN OTHERS THEN
542     --{
543         rollback;
544         retcode := SQLCODE;
545         errbuf  := 'REPORT_MISSING_RATE (' || to_char(l_stmt_num)
546                     || '): '|| substr(SQLERRM, 1,200);
547 
548         bis_collection_utilities.put_line('opi_dbi_res_pkg.get_res_conversion_rate - Error at statement ('
549                     || to_char(l_stmt_num) || ')');
550 
551         bis_collection_utilities.put_line('Error Number: ' ||  retcode );
552         bis_collection_utilities.put_line('Error Message: ' || errbuf  );
553     --}
554 END get_res_conversion_rate;
555 
556 
557 
558 /*===============================================================
559     This procedure extracts resource availability data into
560     the staging table for initial load.
561 
562     Parameters:
563     - p_start_date: lower run bound
564     - p_end_date:   upper run bound
565     - errbuf:   error buffer
566     - retcode:  return code
567 ================================================================*/
568 
569 PROCEDURE initial_opi_res_avail  (p_start_date  IN DATE,
570                                   p_end_date    IN DATE,
571                                   errbuf    IN OUT NOCOPY VARCHAR2,
572                                   retcode   IN OUT NOCOPY VARCHAR2) IS
573     l_stmt_num  NUMBER;
574     l_count     NUMBER;
575 
576 BEGIN
577 
578     bis_collection_utilities.put_line('Enter initial_opi_res_avail() ' ||
579                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
580 
581     retcode := g_ok;
582     l_stmt_num := 10;
583 
584     -- populate availability for 24 hr available resource
585 
586     INSERT /*+ append parallel(e) */ INTO opi_dbi_res_avail_stg (
587             resource_id,
588             department_id,
589             organization_id,
590             transaction_date,
591             uom,
592             avail_qty,
593             avail_qty_g,
594             avail_val_b,
595             source)
596     SELECT /*+  use_hash(m) use_hash(bd) use_hash(bdr) use_hash(br)  use_hash(mp)
597                 use_hash(crc) parallel(m) full(bcd) use_hash(bcd) parallel(br) parallel(bd)
598                 parallel(bdr) parallel(bcd) use_hash(m2) parallel(m2) */
599             br.resource_id,
600             bdr.department_id,
601             br.organization_id,
602             bcd.calendar_date               transaction_date,
603             br.unit_of_measure              uom,
604             24* bdr.capacity_units/m2.conversion_rate  avail_qty,
605             24* bdr.capacity_units          avail_qty_g,
606             24* bdr.capacity_units/m2.conversion_rate  * crc.resource_rate avail_val_b,
607             OPI_SOURCE                      source
608     FROM    bom_resources                   br,
609             bom_departments                 bd,
610             bom_department_resources        bdr,
611             bom_calendar_dates              bcd,
612             mtl_parameters                  mp,
613             mtl_uom_conversions             m,
614             mtl_uom_conversions             m2,
615             cst_resource_costs              crc
616     WHERE   bdr.available_24_hours_flag = 1  -- 24 hr available
617     AND     bdr.share_from_dept_id IS NULL     -- owing dept
618     AND     br.resource_id = bdr.resource_id
619     AND     m.inventory_item_id  = 0
620     AND     m.uom_code           = g_hr_uom
621     AND     m2.uom_code          = br.unit_of_measure
622     AND     m2.uom_class         = m.uom_class
623     AND     m2.inventory_item_id  = 0
624     AND     bd.department_id = bdr.department_id
625     AND     bd.organization_id = mp.organization_id
626     AND     bcd.calendar_code  = mp.calendar_code
627     AND     bcd.exception_set_id = mp.calendar_exception_set_id
628     AND     bcd.seq_num IS NOT NULL           -- scheduled to be on
629     AND     bcd.calendar_date between p_start_date AND p_end_date
630     AND     ( bd.disable_date IS NULL OR bcd.calendar_date < bd.disable_date)
631     AND     ( br.disable_date IS NULL OR bcd.calendar_date < br.disable_date)
632     AND     bcd.calendar_date > ( bdr.creation_date - 1)
633     AND     crc.resource_id      = br.resource_id
634     AND     crc.organization_id  = mp.organization_id
635     AND     ( (mp.primary_cost_method = 1 AND crc.cost_type_id = 1)
636             OR (mp.primary_cost_method in (2,5,6) AND crc.cost_type_id =mp.AVG_RATES_COST_TYPE_ID ) )
637      ;
638 
639      l_count := sql%rowcount;
640 
641      commit;
642 
643      bis_collection_utilities.put_line('24 hr available resource '|| l_count ||
644                     ' rows into stg, completed at ' ||
645                        To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
646 
647      l_stmt_num   := 20;
648      -- populate availability for shift based resource
649 
650     INSERT /*+ append */ INTO opi_dbi_res_avail_stg (
651             resource_id,
652             department_id,
653             organization_id,
654             transaction_date,
655             uom,
656             avail_qty,
657             avail_qty_g,
658             avail_val_b,
659             source)
660     SELECT  br.resource_id,
661             bd.department_id,
662             br.organization_id,
663             Trunc(bsd.shift_date) transaction_date,
664             br.unit_of_measure,
665             sum(case when (bst.to_time >= bst.from_time) then
666             ( (bst.to_time - bst.from_time)/3600*bdr.capacity_units
667             /m2.conversion_rate * m.conversion_rate )
668             else ( ( 86400 - bst.from_time + bst.to_time)/3600*bdr.capacity_units
669             /m2.conversion_rate * m.conversion_rate ) end ) avail_qty,
670             sum(case when (bst.to_time >= bst.from_time) then
671             ( (bst.to_time - bst.from_time)/3600*bdr.capacity_units )
672             else ( ( 86400 - bst.from_time + bst.to_time)/3600*bdr.capacity_units)
673             end )           avail_qty_g,
674             sum(case when (bst.to_time >= bst.from_time) then
675             ( (bst.to_time - bst.from_time)/3600*bdr.capacity_units
676                 /m2.conversion_rate * m.conversion_rate * crc.resource_rate )
677             else ( ( 86400 - bst.from_time + bst.to_time)/3600*bdr.capacity_units
678             /m2.conversion_rate * m.conversion_rate * crc.resource_rate )
679             end )           avail_val_b,
680             OPI_SOURCE  source
681      FROM   bom_resources                   br,
682             bom_departments                 bd,
683             bom_department_resources        bdr,
684             bom_resource_shifts             brs,
685             bom_shift_dates                 bsd,
686             bom_shift_times                 bst,
687             mtl_parameters                  mp,
688             mtl_uom_conversions             m,
689             mtl_uom_conversions             m2,
690             cst_resource_costs              crc
691      WHERE  bdr.available_24_hours_flag = 2   -- shift based
692      AND    bdr.share_from_dept_id IS NULL      -- owning dept
693      AND    br.resource_id = bdr.resource_id
694      AND    m.inventory_item_id  = 0
695      AND    m.uom_code           = g_hr_uom
696      AND    m2.uom_code          = br.unit_of_measure
697      AND    m2.uom_class         = m.uom_class
698      AND    m2.inventory_item_id  = 0
699      AND    bd.department_id = bdr.department_id
700      AND    bd.organization_id = mp.organization_id
701      AND    brs.department_id = bd.department_id
702      AND    brs.resource_id   = br.resource_id
703      AND    bsd.calendar_code = mp.calendar_code
704      AND    bsd.exception_set_id = mp.calendar_exception_set_id
705      AND    bsd.shift_num     = brs.shift_num
706      AND    bsd.seq_num IS NOT NULL               -- schedule to be available
707      AND    bsd.shift_date BETWEEN p_start_date AND p_end_date
708      AND    ( bd.disable_date IS NULL OR bsd.shift_date < bd.disable_date)
709      AND    ( br.disable_date IS NULL OR bsd.shift_date < br.disable_date)
710      AND    bsd.shift_date > ( bdr.creation_date - 1)
711      AND    bst.calendar_code = mp.calendar_code
712      AND    bst.shift_num     = brs.shift_num
713      AND    crc.resource_id      = br.resource_id
714      AND    crc.organization_id  = mp.organization_id
715      AND     ( (mp.primary_cost_method = 1 AND crc.cost_type_id = 1)
716             OR (mp.primary_cost_method =2 AND crc.cost_type_id = mp.AVG_RATES_COST_TYPE_ID ) )
717      GROUP BY
718             br.organization_id, bd.department_id,
719             br.resource_id, br.unit_of_measure,
720             bsd.shift_date;
721 
722      l_count := sql%rowcount;
723 
724      COMMIT;
725      bis_collection_utilities.put_line('shift based available resource '||
726                 l_count ||' rows into stg, completed at ' ||
727                 To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
728 
729     bis_collection_utilities.put_line('initial_opi_res_avail() ' ||
730                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
731 
732 EXCEPTION WHEN OTHERS THEN
733     --{
734     Errbuf:= Sqlerrm;
735     Retcode:= SQLCODE;
736 
737     ROLLBACK;
738 
739     bis_collection_utilities.put_line('Exception in initial_opi_res_avail ' || errbuf );
740     --}
741 END initial_opi_res_avail;
742 
743 
744 /*===============================================================
745     This procedure extracts actual resource usage  data into
746     the staging table for initial load.
747 
748     Parameters:
749     - errbuf:   error buffer
750     - retcode:  return code
751 ================================================================*/
752 
753 PROCEDURE initial_opi_res_actual  (errbuf   IN OUT NOCOPY VARCHAR2,
754                                    retcode  IN OUT NOCOPY VARCHAR2) IS
755     l_stmt_num  NUMBER;
756     l_count     number;
757 
758 BEGIN
759 
760     bis_collection_utilities.put_line('Enter initial_opi_res_actual() ' ||
761                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
762 
763     retcode := g_ok;
764 
765     INSERT /*+ append parallel(a) */ INTO opi_dbi_res_actual_stg a (
766             resource_id,
767             department_id,
768             organization_id,
769             transaction_date,
770             actual_qty_draft,
771             actual_qty,
772             actual_qty_g_draft,
773             actual_qty_g,
774             uom,
775             actual_val_b_draft,
776             actual_val_b,
777             source,
778             job_id,
779             job_type,
780             assembly_item_id)
781     SELECT   /*+ parallel(we) parallel(bdr) parallel(wt) parallel(wta)
782             use_hash(wt) use_hash(we) use_hash(wta)*/
783             wt.resource_id,
784             nvl(bdr.share_from_dept_id,wt.department_id),
785             wt.organization_id,
786             Trunc(wt.transaction_date)      transaction_date,
787             0                               actual_qty_draft,
788             SUM(wt.primary_quantity)        actual_qty,
789             0                               actual_qty_g_draft,
790             SUM(wt.primary_quantity*m2.conversion_rate/m.conversion_rate) actual_qty_g,
791             wt.primary_uom                  uom,
792             0                               actual_val_b_draft,
793             SUM(wta.base_transaction_value * -1)    actual_val_b,
794             OPI_SOURCE                      source,
795             nvl( wta.repetitive_schedule_id, wta.wip_entity_id )    job_id,
796             Decode(we.entity_type, 1, 1, 2, 2, 3, 1, 4, 3, 5, 5, 8, 5, 0)        job_type,
797             wt.primary_item_id              assembly_item_id
798      FROM    wip_transactions                wt,
799             wip_transaction_accounts        wta,
800             wip_entities                    we,
801             mtl_uom_conversions             m,
802             mtl_uom_conversions             m2,
803             opi_dbi_run_log_curr            rlc,
804             bom_department_resources        bdr
805     WHERE
806      -- 1->resource trx   3-> outside processing,
807      -- both involve resource, other types don't have resource_id
808             Rlc.etl_id = ACTUAL_RES_ETL
809     AND     Rlc.source = 1
810     AND     wt.transaction_id >= Rlc.start_txn_id
811     AND     wt.transaction_id < Rlc.next_start_txn_id
812     AND     wt.transaction_type IN (1,3)
813     AND     wta.transaction_id  = wt.transaction_id
814     AND     wta.accounting_line_type = 4
815     AND     we.wip_entity_id = wt.wip_entity_id
816     AND     m.inventory_item_id = 0
817     AND     m.uom_code          = g_hr_uom
818     AND     m2.uom_code = wt.primary_uom
819     AND     m2.inventory_item_id = 0
820     AND     m2.uom_class = m.uom_class
821     and     bdr.resource_id     = wt.resource_id
822     and     bdr.department_id   = wt.department_id
823     GROUP BY
824             wt.resource_id,
825             nvl( bdr.share_from_dept_id,wt.department_id),
826             wt.organization_id,
827             Trunc(wt.transaction_date),
828             wt.primary_uom,
829             wta.repetitive_schedule_id,
830             wta.wip_entity_id ,
831             we.entity_type,
832             wt.primary_item_id;
833 
834     l_count := sql%rowcount;
835 
836     bis_collection_utilities.put_line('resource actual '|| l_count ||
837                 ' rows into stg, completed at ' ||
838                 To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
839 
840     bis_collection_utilities.put_line('Exit initial_opi_res_actual() ' ||
841                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
842 
843     COMMIT;
844 
845 EXCEPTION WHEN OTHERS THEN
846 --{
847     Errbuf:= Sqlerrm;
848     Retcode:= SQLCODE;
849 
850     ROLLBACK;
851 
852     bis_collection_utilities.put_line('Exception in initial_opi_res_actual ' || errbuf );
853 --}
854 
855 END initial_opi_res_actual;
856 
857 
858 /*===============================================================
859     This procedure extracts resource availability data into
860     the staging table for incremental load.
861 
862     Parameters:
863     - p_start_date: lower run bound
864     - p_end_date:   upper run bound
865     - errbuf:   error buffer
866     - retcode:  return code
867 ================================================================*/
868 
869 PROCEDURE incremental_opi_res_avail  (p_start_date  IN DATE,
870                                       p_end_date    IN DATE,
871                                       errbuf    IN OUT NOCOPY VARCHAR2,
872                                       retcode   IN OUT NOCOPY VARCHAR2) IS
873     l_stmt_num  NUMBER;
874     l_count     number;
875 
876     l_start_date date;
877     l_end_date   date;
878 
879 BEGIN
880 
881     bis_collection_utilities.put_line('Enter incremental_opi_res_avail() ' ||
882                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
883 
884     retcode := g_ok;
885 
886     l_start_date := p_start_date;
887     l_end_date := p_end_date;
888 
889     l_stmt_num := 10;
890 
891     -- if from_date is not to_date, start from the day after from_date
892     IF (l_start_date <> l_end_date) THEN
893     --{
894         l_start_date := l_start_date + 1;
895     --}
896     END IF;
897 
898 
899     -- populate availability for 24 hr available resource
900     INSERT INTO opi_dbi_res_avail_stg (
901             resource_id,
902             department_id,
903             organization_id,
904             transaction_date,
905             uom,
906             avail_qty,
907             avail_qty_g,
908             avail_val_b,
909             source)
910     SELECT  br.resource_id,
911             bd.department_id,
912             br.organization_id,
913             bcd.calendar_date               transaction_date,
914             br.unit_of_measure           uom,
915             24* bdr.capacity_units/m2.conversion_rate  avail_qty,
916             24* bdr.capacity_units          avail_qty_g,
917             24* bdr.capacity_units/m2.conversion_rate  * crc.resource_rate avail_val_b,
918             OPI_SOURCE  source
919     FROM    bom_resources                   br,
920             bom_departments                 bd,
921             bom_department_resources        bdr,
922             bom_calendar_dates              bcd,
923             mtl_parameters                  mp,
924             mtl_uom_conversions             m,
925             mtl_uom_conversions             m2,
926             cst_resource_costs              crc
927     WHERE   bdr.available_24_hours_flag = 1  -- 24 hr available
928     AND     bdr.share_from_dept_id IS NULL     -- owing dept
929     AND     br.resource_id = bdr.resource_id
930     AND     m.inventory_item_id  = 0
931     AND     m.uom_code           =g_hr_uom
932     AND     m2.uom_code          = br.unit_of_measure
933     AND     m2.uom_class         = m.uom_class
934     AND     m2.inventory_item_id  = 0
935     AND     bd.department_id = bdr.department_id
936     AND     bd.organization_id = mp.organization_id
937     AND     bcd.calendar_code  = mp.calendar_code
938     AND     bcd.exception_set_id = mp.calendar_exception_set_id
939     AND     bcd.seq_num IS NOT NULL           -- scheduled to be on
940     AND     bcd.calendar_date between l_start_date AND l_end_date
941     AND     ( bd.disable_date IS NULL OR bcd.calendar_date < bd.disable_date)
942     AND     ( br.disable_date IS NULL OR bcd.calendar_date < br.disable_date)
943     and     bcd.calendar_date > ( bdr.creation_date - 1)
944     AND     crc.resource_id      = br.resource_id
945     AND     crc.organization_id  = mp.organization_id
946     AND     ( (mp.primary_cost_method = 1 AND crc.cost_type_id = 1)
947             OR (mp.primary_cost_method =2 AND crc.cost_type_id =mp.AVG_RATES_COST_TYPE_ID ) )
948     ;
949 
950     l_count := sql%rowcount;
951 
952     bis_collection_utilities.put_line('24 hr available resource '|| l_count ||
953                 ' rows into stg, completed at ' ||
954                    To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
955 
956     l_stmt_num   := 20;
957     -- populate availability for shift based resource
958 
959     INSERT INTO opi_dbi_res_avail_stg (
960             resource_id,
961             department_id,
962             organization_id,
963             transaction_date,
964             uom,
965             avail_qty,
966             avail_qty_g,
967             avail_val_b,
968             source)
969      SELECT  br.resource_id,
970             bd.department_id,
971             br.organization_id,
972             Trunc(bsd.shift_date) transaction_date,
973             br.unit_of_measure,
974             sum(case when (bst.to_time >= bst.from_time) then
975             ( (bst.to_time - bst.from_time)/3600*bdr.capacity_units
976             /m2.conversion_rate * m.conversion_rate )
977             else ( ( 86400 - bst.from_time + bst.to_time)/3600*bdr.capacity_units
978             /m2.conversion_rate * m.conversion_rate ) end ) avail_qty,
979             sum(case when (bst.to_time >= bst.from_time) then
980             ( (bst.to_time - bst.from_time)/3600*bdr.capacity_units )
981             else ( ( 86400 - bst.from_time + bst.to_time)/3600*bdr.capacity_units)
982             end  ) avail_qty_g,
983             sum(case when (bst.to_time >= bst.from_time) then
984             ( (bst.to_time - bst.from_time)/3600*bdr.capacity_units
985             /m2.conversion_rate * m.conversion_rate * crc.resource_rate )
986             else ( ( 86400 - bst.from_time + bst.to_time)/3600*bdr.capacity_units
987             /m2.conversion_rate * m.conversion_rate * crc.resource_rate )
988             end ) avail_val_b,
989             OPI_SOURCE source
990      FROM   bom_resources                   br,
991             bom_departments                 bd,
992             bom_department_resources        bdr,
993             bom_resource_shifts             brs,
994             bom_shift_dates                 bsd,
995             bom_shift_times                 bst,
996             mtl_parameters                  mp,
997             mtl_uom_conversions             m,
998             mtl_uom_conversions             m2,
999             cst_resource_costs              crc
1000     WHERE   bdr.available_24_hours_flag = 2   -- shift based
1001     AND     bdr.share_from_dept_id IS NULL      -- owning dept
1002     AND     br.resource_id = bdr.resource_id
1003     AND     m.inventory_item_id  = 0
1004     AND     m.uom_code           = g_hr_uom
1005     AND     m2.uom_code          = br.unit_of_measure
1006     AND     m2.uom_class         = m.uom_class
1007     AND     m2.inventory_item_id  = 0
1008     AND     bd.department_id = bdr.department_id
1009     AND     bd.organization_id = mp.organization_id
1010     AND     brs.department_id = bd.department_id
1011     AND     brs.resource_id   = br.resource_id
1012     AND     bsd.calendar_code = mp.calendar_code
1013     AND     bsd.exception_set_id = mp.calendar_exception_set_id
1014     AND     bsd.shift_num     = brs.shift_num
1015     AND     bsd.seq_num IS NOT NULL               -- schedule to be available
1016     AND     bsd.shift_date BETWEEN l_start_date AND l_end_date
1017     AND     ( bd.disable_date IS NULL OR bsd.shift_date < bd.disable_date)
1018     AND     ( br.disable_date IS NULL OR bsd.shift_date < br.disable_date)
1019     AND     bsd.shift_date > ( bdr.creation_date - 1)
1020     AND     bst.calendar_code = mp.calendar_code
1021     AND     bst.shift_num     = brs.shift_num
1022     AND     crc.resource_id      = br.resource_id
1023     AND     crc.organization_id  = mp.organization_id
1024     AND     ( (mp.primary_cost_method = 1 AND crc.cost_type_id = 1)
1025             OR (mp.primary_cost_method in (2,5,6) AND crc.cost_type_id = mp.AVG_RATES_COST_TYPE_ID ) )
1026     GROUP BY
1027             br.organization_id, bd.department_id,
1028             br.resource_id, br.unit_of_measure,
1029             bsd.shift_date;
1030 
1031     l_count := sql%rowcount;
1032 
1033     bis_collection_utilities.put_line('shift based available resource '||
1034                  l_count ||' rows into stg, completed at ' ||
1035                  To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1036 
1037     bis_collection_utilities.put_line('Exit incremental_opi_res_avail() ' ||
1038                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1039 
1040 EXCEPTION WHEN OTHERS THEN
1041 --{
1042     Errbuf:= Sqlerrm;
1043     Retcode:= SQLCODE;
1044 
1045     ROLLBACK;
1046 
1047     bis_collection_utilities.put_line('Exception in incremental_opi_res_avail ' || errbuf );
1048 --}
1049 END incremental_opi_res_avail;
1050 
1051 
1052 /*===============================================================
1053     This procedure extracts actual resource usage  data into
1054     the staging table for incremental load.
1055 
1056     Parameters:
1057     - errbuf:   error buffer
1058     - retcode:  return code
1059 ================================================================*/
1060 
1061 PROCEDURE incremental_opi_res_actual  (errbuf   IN OUT NOCOPY VARCHAR2,
1062                                        retcode  IN OUT NOCOPY VARCHAR2) IS
1063     l_stmt_num  NUMBER;
1064     l_transaction_id NUMBER;
1065     l_count     number;
1066 
1067 BEGIN
1068 
1069     bis_collection_utilities.put_line('Enter incremental_opi_res_actual() ' ||
1070                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1071 
1072     retcode := g_ok;
1073 
1074     INSERT INTO opi_dbi_res_actual_stg (
1075             resource_id,
1076             department_id,
1077             organization_id,
1078             transaction_date,
1079             actual_qty_draft,
1080             actual_qty,
1081             actual_qty_g_draft,
1082             actual_qty_g,
1083             uom,
1084             actual_val_b_draft,
1085             actual_val_b,
1086             source,
1087             job_id,
1088             job_type,
1089             assembly_item_id)
1090     SELECT  /*+ ordered use_nl(rlc wt) index(rlc, OPI_DBI_RUN_LOG_CURR_N1)
1091             index(wt, WIP_TRANSACTIONS_U1) index(wta, WIP_TRANSACTION_ACCOUNTS_N1)
1092             use_nl(we) index(we, WE_C1) index(bdr, BOM_DEPARTMENT_RESOURCES_U1)
1093             use_nl(bdr) use_nl(m) use_nl(m2) */
1094             wt.resource_id,
1095             nvl(bdr.share_from_dept_id, wt.department_id ),
1096             wt.organization_id,
1097             Trunc(wt.transaction_date)  transaction_date,
1098             0                           actual_qty_draft,
1099             SUM(wt.primary_quantity)    actual_qty,
1100             0                           actual_qty_g_draft,
1101             SUM(wt.primary_quantity*m2.conversion_rate/m.conversion_rate) actual_qty_g,
1102             wt.primary_uom              uom,
1103             0                           actual_val_b_draft,
1104             SUM(wta.base_transaction_value * -1)  actual_val_b,
1105             OPI_SOURCE                  source,
1106             nvl( wta.repetitive_schedule_id, wta.wip_entity_id )    job_id,
1107             Decode(we.entity_type, 1, 1, 2, 2, 3, 1, 4, 3, 5, 5, 8, 5, 0)        job_type,
1108              wt.primary_item_id          assembly_item_id
1109     FROM    wip_transactions                wt,
1110             wip_transaction_accounts        wta,
1111             wip_entities                    we,
1112             opi_dbi_run_log_curr            rlc,
1113             bom_department_resources        bdr,
1114             mtl_uom_conversions             m,
1115             mtl_uom_conversions             m2
1116     WHERE
1117      -- 1->resource trx   3-> outside processing,
1118      -- both involve resource, other types don't have resource_id
1119             Rlc.etl_id = ACTUAL_RES_ETL
1120     AND     Rlc.source = 1
1121     AND     wt.transaction_id >= Rlc.start_txn_id
1122     AND     wt.transaction_id < Rlc.next_start_txn_id
1123     AND     wt.transaction_type IN (1,3)
1124     AND     wta.transaction_id  = wt.transaction_id
1125     AND     wta.accounting_line_type = 4
1126     AND     we.wip_entity_id = wt.wip_entity_id
1127     AND     m.inventory_item_id = 0
1128     AND     m.uom_code = g_hr_uom
1129     AND     m2.uom_code = wt.primary_uom
1130     AND     m2.inventory_item_id = 0
1131     AND     m2.uom_class = m.uom_class
1132     AND     bdr.resource_id     = wt.resource_id
1133     AND     bdr.department_id   = wt.department_id
1134     GROUP BY
1135             wt.resource_id,
1136             nvl(bdr.share_from_dept_id,wt.department_id),
1137             wt.organization_id,
1138             Trunc(wt.transaction_date),
1139             wt.primary_uom,
1140             wta.repetitive_schedule_id,
1141             wta.wip_entity_id,
1142             we.entity_type,
1143             wt.primary_item_id;
1144 
1145     l_count := sql%rowcount;
1146 
1147     bis_collection_utilities.put_line('incremental load of actual resource '||
1148                  l_count ||' rows into stg, completed at ' ||
1149                  To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1150 
1151     bis_collection_utilities.put_line('Exit incremental_opi_res_actual() ' ||
1152                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1153 
1154 EXCEPTION WHEN OTHERS THEN
1155 --{
1156     Errbuf:= Sqlerrm;
1157     Retcode:= SQLCODE;
1158 
1159     ROLLBACK;
1160 
1161     bis_collection_utilities.put_line('Exception in incremental_opi_res_actual ' || errbuf );
1162 --}
1163 END incremental_opi_res_actual;
1164 
1165 
1166 
1167 /*======================================================
1168     This procedure extracts actual resource usage data
1169     into the staging table for initial load.
1170 
1171     Parameters:
1172     - errbuf: error buffer
1173     - retcode: return code
1174 =======================================================*/
1175 
1176 PROCEDURE initial_opm_res_actual  (errbuf   IN OUT NOCOPY VARCHAR2,
1177                                    retcode  IN OUT NOCOPY VARCHAR2) IS
1178    l_stmt_num  NUMBER;
1179    l_rowcount NUMBER;
1180 
1181 BEGIN
1182 
1183     bis_collection_utilities.put_line('Enter initial_opm_res_actual() ' ||
1184                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1185 
1186     retcode := g_ok;
1187 
1188     INSERT /*+ APPEND */ INTO opi_dbi_res_actual_stg (
1189             resource_id,
1190             organization_id,
1191             transaction_date,
1192             uom,
1193             actual_qty_draft,
1194             actual_qty,
1195             actual_qty_g_draft,
1196             actual_qty_g,
1197             actual_val_b_draft,
1198             actual_val_b,
1199             source,
1200             job_id,
1201             job_type,
1202             assembly_item_id,
1203             department_id)
1204     SELECT  rdtl.resource_id                resource_id,
1205             rtran.organization_id              organization_id,
1206             trunc(rtran.trans_date)         transaction_date,
1207             rtran.trans_qty_um                  uom,
1208             sum(decode(gtv.accounted_flag, 'D', rtran.resource_usage * prod.cost_alloc, 0)) actual_qty_draft,
1209             sum(decode(gtv.accounted_flag, 'D', 0, rtran.resource_usage * prod.cost_alloc)) actual_qty,
1210             sum(decode(gtv.accounted_flag, 'D',
1211               rtran.resource_usage * prod.cost_alloc * hruom.std_factor/ruom.std_factor, 0)) actual_qty_g_draft,
1212             sum(decode(gtv.accounted_flag, 'D', 0,
1213               rtran.resource_usage * prod.cost_alloc * hruom.std_factor/ruom.std_factor))   actual_qty_g,
1214             sum(decode(gtv.accounted_flag, 'D', gtv.txn_base_value * prod.cost_alloc, 0))     actual_val_b_draft,
1215             sum(decode(gtv.accounted_flag, 'D', 0, gtv.txn_base_value * prod.cost_alloc)) actual_val_b,
1216             OPM_SOURCE                      source,
1217             rtran.doc_id                    job_id,
1218             4                               job_type,
1219             prod.inventory_item_id           assembly_item_id,
1220             rmst.resource_class             department_id
1221     FROM    sy_uoms_mst                 hruom,
1222             sy_uoms_mst                 ruom,
1223             gme_resource_txns           rtran,
1224             cr_rsrc_dtl                 rdtl,
1225             cr_rsrc_mst_b               rmst,
1226             gme_material_details        prod,
1227             (
1228             SELECT  gtv.transaction_id,
1229                     gtv.accounted_flag,
1230                     gtv.txn_base_value
1231             FROM    gmf_transaction_valuation   gtv,
1232                     opi_dbi_run_log_curr        log,
1233                     opi_dbi_org_le_temp         tmp
1234             WHERE   nvl(gtv.accounted_flag, 'F') <> 'N'
1235             AND     gtv.journal_line_type = 'WIP'
1236             AND     gtv.event_class_code = 'BATCH_RESOURCE'
1237             AND     gtv.transaction_date >= g_global_start_date
1238             AND     nvl(gtv.final_posting_date, log.from_bound_date) >= log.from_bound_date
1239             AND     nvl(gtv.final_posting_date, log.from_bound_date) < log.to_bound_date
1240             AND     log.etl_id = ACTUAL_RES_ETL
1241             AND     log.source = OPM_SOURCE
1242             AND     gtv.ledger_id = tmp.ledger_id
1243             AND     gtv.legal_entity_id = tmp.legal_entity_id
1244             AND     gtv.valuation_cost_type_id = tmp.valuation_cost_type_id
1245             AND     gtv.organization_id = tmp.organization_id) gtv
1246     WHERE   hruom.uom_code = g_hr_uom
1247     AND     ruom.uom_code = rtran.trans_qty_um
1248     AND     gtv.transaction_id = rtran.poc_trans_id
1249     AND     rtran.completed_ind = 1
1250     AND     rdtl.organization_id = rtran.organization_id
1251     AND     rdtl.resources = rtran.resources
1252     AND     rmst.resources = rdtl.resources
1253     AND     prod.batch_id = rtran.doc_id
1254     AND     prod.line_type = 1
1255     GROUP BY
1256             prod.inventory_item_id,
1257             rtran.doc_id,
1258             rdtl.resource_id,
1259             rmst.resource_class,
1260             trunc(rtran.trans_date),
1261             rtran.trans_qty_um,
1262             rtran.organization_id;
1263 
1264     commit;
1265     l_rowcount := sql%rowcount;
1266 
1267     bis_collection_utilities.put_line('OPM Resource Actual: ' ||
1268              l_rowcount || ' rows initially collected into staging table at '||
1269              to_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1270 
1271     bis_collection_utilities.put_line('Exit initial_opm_res_actual() ' ||
1272                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1273 
1274 
1275 EXCEPTION WHEN OTHERS THEN
1276 --{
1277    Errbuf:= Sqlerrm;
1278    Retcode:= SQLCODE;
1279 
1280    ROLLBACK;
1281 
1282    bis_collection_utilities.put_line('Exception in initial_opm_res_actual ' || errbuf );
1283 --}
1284 END initial_opm_res_actual;
1285 
1286 
1287 
1288 /*======================================================
1289     This procedure extracts resource availability data
1290     into the staging table for initial load.
1291 
1292     Parameters:
1293     - p_start_date: lower run bound
1294     - p_end_date:   upper run bound
1295     - errbuf: error buffer
1296     - retcode: return code
1297 =======================================================*/
1298 
1299 PROCEDURE initial_opm_res_avail  (p_start_date  IN DATE,
1300                                   p_end_date    IN DATE,
1301                                   errbuf        IN OUT NOCOPY VARCHAR2,
1302                                   retcode       IN OUT NOCOPY VARCHAR2)
1303 IS
1304     l_stmt_num  NUMBER;
1305     l_rowcount NUMBER;
1306 
1307 BEGIN
1308 
1309     bis_collection_utilities.put_line('Enter initial_opm_res_avail() ' ||
1310                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1311 
1312     retcode := g_ok;
1313     l_stmt_num := 10;
1314 
1315     -- populate availability for opm resource
1316 
1317      INSERT /*+ APPEND */ INTO opi_dbi_res_avail_stg (
1318             resource_id,
1319             organization_id,
1320             department_id,
1321             transaction_date,
1322             uom,
1323             avail_qty,
1324             avail_qty_g,
1325             avail_val_b,
1326             source)
1327     SELECT
1328             r.resource_id           resource_id,
1329             r.organization_id       organization_id,
1330             r.department_id         department_id,
1331             r.shift_date            transaction_date,
1332             r.usage_uom              uom,
1333             SUM(r.shift_hours * hruom.std_factor / ruom.std_factor)
1334                                 avail_qty,
1335             SUM(r.shift_hours)      avail_qty_g, -- availability in hours
1336             SUM(r.shift_hours * hruom.std_factor / rcostuom.std_factor * rcost.nominal_cost)
1337                                 avail_val_b,
1338             OPM_SOURCE                       source
1339     FROM
1340     (
1341             SELECT
1342                     mp.organization_id,
1343                     rdtl.resources,
1344                     rdtl.resource_id,
1345                     rmst.resource_class department_id,
1346                     rdtl.usage_uom,
1347                     pol.cost_type_id,
1348                     cmm.default_lot_cost_type_id,
1349                     pol.legal_entity_id,
1350                     ravail.shift_date,
1351                     sum((ravail.to_time - ravail.from_time)*ravail.resource_units/3600) shift_hours
1352             FROM    cr_rsrc_dtl         rdtl,
1353                     cr_rsrc_mst_b       rmst,
1354                     gmf_fiscal_policies pol,
1355                     mtl_parameters      mp,
1356                     gmp_resource_avail  ravail,
1357                     org_organization_definitions    org_def,
1358                     cm_mthd_mst cmm
1359             WHERE   rmst.resources = rdtl.resources
1360             AND     rdtl.organization_id = org_def.organization_id
1361             AND     org_def.legal_entity = pol.legal_entity_id
1362             AND     ravail.calendar_code = mp.calendar_code
1363             AND     ravail.organization_id = mp.organization_id
1364             AND     ravail.organization_id = rdtl.organization_id
1365             AND     ravail.resource_id = rdtl.resource_id
1366             AND     nvl(ravail.instance_id,0) = 0 -- resource level row
1367             AND     NVL(ravail.resource_instance_id,0) = 0 -- exclude individual resource instances
1368             AND     ravail.shift_date BETWEEN p_start_date AND p_end_date
1369             AND     ravail.shift_date >= trunc(rdtl.creation_date)
1370             AND     pol.cost_type_id = cmm.cost_type_id
1371             GROUP BY
1372                     rdtl.resources,
1373                     rdtl.resource_id,
1374                     rmst.resource_class,
1375                     rdtl.usage_uom,
1376                     pol.cost_type_id,
1377                     pol.legal_entity_id,
1378                     mp.organization_id,
1379                     ravail.shift_date,
1380                     cmm.default_lot_cost_type_id
1381             ) r,
1382             (
1383             SELECT  period.cost_type_id,
1384                     period.legal_entity_id,
1385                     period.period_id,
1386                     period.start_date,
1387                     period.end_date
1388             FROM    gmf_period_statuses period
1389             WHERE   period.end_date >= p_start_date
1390             AND     period.start_date <= p_end_date
1391             ) cal,
1392             sy_uoms_mst_v ruom,
1393             sy_uoms_mst_v rcostuom,
1394             sy_uoms_mst_v hruom,
1395             cm_rsrc_dtl rcost
1396     WHERE   cal.cost_type_id in (r.cost_type_id, r.default_lot_cost_type_id)
1397     AND     r.legal_entity_id = cal.legal_entity_id
1398     AND     r.shift_date BETWEEN cal.start_date AND cal.end_date
1399     AND     rcost.organization_id = r.organization_id
1400     AND     rcost.resources = r.resources
1401     AND     rcost.cost_type_id = cal.cost_type_id
1402     AND     rcost.period_id = cal.period_id
1403     AND     hruom.uom_code = g_hr_uom
1404     AND     ruom.uom_code = r.usage_uom
1405     AND     rcostuom.uom_code = rcost.usage_uom
1406     GROUP BY
1407             r.resource_id,
1408             r.organization_id,
1409             r.department_id,
1410             r.shift_date,
1411             r.usage_uom;
1412 
1413     l_rowcount := sql%rowcount;
1414 
1415     COMMIT;
1416 
1417     bis_collection_utilities.put_line('OPM Resource Availability: ' ||
1418              l_rowcount || ' rows initially collected into staging table at '||
1419              to_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1420 
1421     bis_collection_utilities.put_line('Exit initial_opm_res_avail() ' ||
1422                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1423 
1424 EXCEPTION WHEN OTHERS THEN
1425 --{
1426    errbuf:= Sqlerrm;
1427    retcode:= SQLCODE;
1428 
1429    ROLLBACK;
1430 
1431    bis_collection_utilities.put_line('Exception in initial_opm_res_avail ' || errbuf );
1432 --}
1433 END initial_opm_res_avail;
1434 
1435 
1436 /*======================================================
1437     This procedure extracts actual resource usage data
1438     into the staging table for incremental load.
1439 
1440     Parameters:
1441     - errbuf: error buffer
1442     - retcode: return code
1443 =======================================================*/
1444 
1445 PROCEDURE incremental_opm_res_actual  ( errbuf  IN OUT NOCOPY VARCHAR2,
1446                                         retcode IN OUT NOCOPY VARCHAR2) IS
1447     l_stmt_num  NUMBER;
1448     l_rowcount NUMBER;
1449 
1450 BEGIN
1451 
1452     bis_collection_utilities.put_line('Enter incremental_opm_res_actual() ' ||
1453                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1454 
1455     retcode := g_ok;
1456 
1457     INSERT /*+ APPEND */ INTO opi_dbi_res_actual_stg (
1458             resource_id,
1459             organization_id,
1460             transaction_date,
1461             uom,
1462             actual_qty_draft,
1463             actual_qty,
1464             actual_qty_g_draft,
1465             actual_qty_g,
1466             actual_val_b_draft,
1467             actual_val_b,
1468             source,
1469             job_id,
1470             job_type,
1471             assembly_item_id,
1472             department_id)
1473     SELECT  rdtl.resource_id                resource_id,
1474             rtran.organization_id              organization_id,
1475             trunc(rtran.trans_date)         transaction_date,
1476             rtran.trans_qty_um                  uom,
1477             sum(decode(gtv.accounted_flag, 'D', rtran.resource_usage * prod.cost_alloc, 0)) actual_qty_draft,
1478             sum(decode(gtv.accounted_flag, 'D', 0, rtran.resource_usage * prod.cost_alloc)) actual_qty,
1479             sum(decode(gtv.accounted_flag, 'D',
1480               rtran.resource_usage * prod.cost_alloc * hruom.std_factor/ruom.std_factor, 0)) actual_qty_g_draft,
1481             sum(decode(gtv.accounted_flag, 'D', 0,
1482               rtran.resource_usage * prod.cost_alloc * hruom.std_factor/ruom.std_factor))   actual_qty_g,
1483             sum(decode(gtv.accounted_flag, 'D', gtv.txn_base_value * prod.cost_alloc, 0))  actual_val_b_draft,
1484             sum(decode(gtv.accounted_flag, 'D', 0, gtv.txn_base_value * prod.cost_alloc))  actual_val_b,
1485             OPM_SOURCE                      source,
1486             rtran.doc_id                    job_id,
1487             4                               job_type,
1488             prod.inventory_item_id           assembly_item_id,
1489             rmst.resource_class             department_id
1490     FROM    sy_uoms_mst                 hruom,
1491             sy_uoms_mst                 ruom,
1492             gme_resource_txns           rtran,
1493             cr_rsrc_dtl                 rdtl,
1494             cr_rsrc_mst_b               rmst,
1495             gme_material_details        prod,
1496             (
1497             SELECT  gtv.transaction_id,
1498                     gtv.accounted_flag,
1499                     gtv.txn_base_value
1500             FROM    gmf_transaction_valuation   gtv,
1501                     opi_dbi_run_log_curr        log,
1502                     opi_dbi_org_le_temp         tmp
1503             WHERE   gtv.accounted_flag is NULL
1504             AND     gtv.journal_line_type = 'WIP'
1505             AND     gtv.event_class_code = 'BATCH_RESOURCE'
1506             AND     gtv.transaction_date >= g_global_start_date
1507             AND     gtv.final_posting_date >= log.from_bound_date
1508             AND     gtv.final_posting_date < log.to_bound_date
1509             AND     log.etl_id = ACTUAL_RES_ETL
1510             AND     log.source = OPM_SOURCE
1511             AND     gtv.ledger_id = tmp.ledger_id
1512             AND     gtv.legal_entity_id = tmp.legal_entity_id
1513             AND     gtv.valuation_cost_type_id = tmp.valuation_cost_type_id
1514             AND     gtv.organization_id = tmp.organization_id
1515             UNION ALL
1516             SELECT  gtv.transaction_id,
1517                     gtv.accounted_flag,
1518                     gtv.txn_base_value
1519             FROM    gmf_transaction_valuation gtv,
1520                     opi_dbi_org_le_temp     tmp
1521             WHERE   gtv.accounted_flag = 'D'
1522             AND     gtv.journal_line_type = 'WIP'
1523             AND     gtv.event_class_code = 'BATCH_RESOURCE'
1524             AND     gtv.transaction_date >= g_global_start_date
1525             AND     gtv.ledger_id = tmp.ledger_id
1526             AND     gtv.legal_entity_id = tmp.legal_entity_id
1527             AND     gtv.valuation_cost_type_id = tmp.valuation_cost_type_id
1528             AND     gtv.organization_id = tmp.organization_id) gtv
1529     WHERE   hruom.uom_code = g_hr_uom
1530     AND     ruom.uom_code = rtran.trans_qty_um
1531     AND     gtv.transaction_id = rtran.poc_trans_id
1532     AND     rtran.completed_ind = 1
1533     AND     rdtl.organization_id = rtran.organization_id
1534     AND     rdtl.resources = rtran.resources
1535     AND     rmst.resources = rdtl.resources
1536     AND     prod.batch_id = rtran.doc_id
1537     AND     prod.line_type = 1
1538     GROUP BY
1539             prod.inventory_item_id,
1540             rtran.doc_id,
1541             rdtl.resource_id,
1542             rmst.resource_class,
1543             trunc(rtran.trans_date),
1544             rtran.trans_qty_um,
1545             rtran.organization_id;
1546 
1547     l_rowcount := sql%rowcount;
1548 
1549     COMMIT;
1550 
1551     bis_collection_utilities.put_line('OPM resource actuals: ' ||
1552                l_rowcount || ' rows incrementally collected into staging table at ' ||
1553                To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1554 
1555     bis_collection_utilities.put_line('Exit incremental_opm_res_actual() ' ||
1556                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1557 
1558 EXCEPTION WHEN OTHERS THEN
1559 --{
1560    errbuf:= Sqlerrm;
1561    retcode:= SQLCODE;
1562 
1563    ROLLBACK;
1564 
1565    bis_collection_utilities.put_line('Exception in incremental_opm_res_actual ' || errbuf );
1566 --}
1567 END incremental_opm_res_actual;
1568 
1569 
1570 /*======================================================
1571     This procedure extracts resource availability data
1572     into the staging table for incremental load.
1573 
1574     Parameters:
1575     - p_start_date: lower run bound
1576     - p_end_date:   upper run bound
1577     - errbuf: error buffer
1578     - retcode: return code
1579 =======================================================*/
1580 
1581 PROCEDURE incremental_opm_res_avail  (p_start_date  IN DATE,
1582                                       p_end_date    IN DATE,
1583                                       errbuf        IN OUT NOCOPY VARCHAR2,
1584                                       retcode       IN OUT NOCOPY VARCHAR2)
1585 IS
1586 
1587     l_stmt_num  NUMBER;
1588     l_rowcount  NUMBER;
1589     l_start_date DATE;
1590     l_end_date   DATE;
1591 
1592 BEGIN
1593 
1594     bis_collection_utilities.put_line('Enter incremental_opm_res_avail() ' ||
1595                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1596 
1597     retcode := g_ok;
1598     l_stmt_num := 10;
1599 
1600     l_start_date := p_start_date;
1601     l_end_date := p_end_date;
1602 
1603     -- if start_date is not end_date,
1604     -- start from the day after start_date
1605 
1606     IF (l_start_date <> l_end_date) THEN
1607     --{
1608         l_start_date := l_start_date + 1;
1609     --}
1610     END IF;
1611 
1612 
1613     -- populate availability for opm resource
1614 
1615      INSERT INTO opi_dbi_res_avail_stg (
1616             resource_id,
1617             organization_id,
1618             department_id,
1619             transaction_date,
1620             uom,
1621             avail_qty,
1622             avail_qty_g,
1623             avail_val_b,
1624             source)
1625     SELECT  r.resource_id            resource_id,
1626             r.organization_id        organization_id,
1627             r.department_id          department_id,
1628             r.shift_date             transaction_date,
1629             r.usage_uom               uom,
1630             SUM(r.shift_hours * hruom.std_factor / ruom.std_factor)
1631                                 avail_qty,
1632             SUM(r.shift_hours) avail_qty_g, -- availability in hours
1633             SUM(r.shift_hours * hruom.std_factor / rcostuom.std_factor * rcost.nominal_cost)
1634                                  avail_val_b,
1635             OPM_SOURCE                         source
1636     FROM    (
1637             SELECT  mp.organization_id,
1638                     rdtl.resources,
1639                     rdtl.resource_id,
1640                     rmst.resource_class department_id,
1641                     rdtl.usage_uom,
1642                     pol.cost_type_id,
1643                     cmm.default_lot_cost_type_id,
1644                     pol.legal_entity_id,
1645                     ravail.shift_date,
1646                     SUM((ravail.to_time - ravail.from_time)*ravail.resource_units/3600) shift_hours
1647             FROM    cr_rsrc_dtl     rdtl,
1648                     cr_rsrc_mst_b   rmst,
1649                     gmf_fiscal_policies pol,
1650                     gmp_resource_avail  ravail,
1651                     mtl_parameters              mp,
1652                     org_organization_definitions    org_def,
1653                     cm_mthd_mst cmm
1654             WHERE   rmst.resources = rdtl.resources
1655             AND     rdtl.organization_id = org_def.organization_id
1656             AND     org_def.legal_entity = pol.legal_entity_id
1657             AND     ravail.calendar_code = mp.calendar_code
1658             AND     ravail.organization_id = mp.organization_id
1659             AND     ravail.organization_id = rdtl.organization_id
1660             AND     ravail.resource_id = rdtl.resource_id
1661             AND     nvl(ravail.instance_id,0) = 0 -- resource level row
1662             AND     NVL(ravail.resource_instance_id,0) = 0 -- exclude individual resource instances
1663             AND     ravail.shift_date BETWEEN l_start_date AND l_end_date
1664             AND     ravail.shift_date >= trunc(rdtl.creation_date)
1665             AND     pol.cost_type_id = cmm.cost_type_id
1666             GROUP BY
1667                     rdtl.resources,
1668                     rdtl.resource_id,
1669                     rmst.resource_class,
1670                     rdtl.usage_uom,
1671                     pol.cost_type_id,
1672                     pol.legal_entity_id,
1673                     mp.organization_id,
1674                     ravail.shift_date,
1675                     cmm.default_lot_cost_type_id
1676             ) r,
1677               (
1678             SELECT  period.cost_type_id,
1679                     period.legal_entity_id,
1680                     period.period_id,
1681                     period.start_date,
1682                     period.end_date
1683             FROM    gmf_period_statuses period
1684             WHERE   period.end_date >= l_start_date
1685             AND     period.start_date <= l_end_date
1686             ) cal,
1687             sy_uoms_mst_v ruom,
1688             sy_uoms_mst_v rcostuom,
1689             sy_uoms_mst_v hruom,
1690             cm_rsrc_dtl rcost
1691     WHERE   cal.cost_type_id in (r.cost_type_id, r.default_lot_cost_type_id)
1692     AND     r.legal_entity_id = cal.legal_entity_id
1693     AND     r.shift_date BETWEEN cal.start_date AND cal.end_date
1694     AND     rcost.organization_id = r.organization_id
1695     AND     rcost.resources = r.resources
1696     AND     rcost.cost_type_id = cal.cost_type_id
1697     AND     rcost.period_id = cal.period_id
1698     AND     hruom.uom_code = g_hr_uom
1699     AND     ruom.uom_code = r.usage_uom
1700     AND     rcostuom.uom_code = rcost.usage_uom
1701     GROUP BY
1702             r.resource_id,
1703             r.organization_id,
1704             r.department_id,
1705             r.shift_date,
1706             r.usage_uom;
1707 
1708     l_rowcount := sql%rowcount;
1709 
1710     COMMIT;
1711 
1712     bis_collection_utilities.put_line('OPM resource availability: ' ||
1713                l_rowcount || ' rows incrementally collected into staging table at ' ||
1714                To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1715 
1716      bis_collection_utilities.put_line('Exit incremental_opm_res_avail() ' ||
1717                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1718 
1719 EXCEPTION WHEN OTHERS THEN
1720 --{
1721     errbuf:= Sqlerrm;
1722     retcode:= SQLCODE;
1723 
1724    ROLLBACK;
1725 
1726    bis_collection_utilities.put_line('Exception in incremental_opm_res_avail ' || errbuf );
1727 --}
1728 END incremental_opm_res_avail;
1729 
1730 
1731 
1732 /*======================================================
1733     This procedure extracts standard resource usage data
1734     into the staging table for initial load.
1735 
1736     Parameters:
1737     - errbuf: error buffer
1738     - retcode: return code
1739 =======================================================*/
1740 
1741 PROCEDURE initial_opm_res_std  (errbuf  IN OUT NOCOPY VARCHAR2,
1742                                 retcode IN OUT NOCOPY VARCHAR2,
1743                                 p_degree IN NUMBER    ) IS
1744     l_stmt_num NUMBER;
1745     l_rowcount NUMBER;
1746 
1747 BEGIN
1748 
1749     bis_collection_utilities.put_line('Enter initial_opm_res_std() ' ||
1750                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1751 
1752     INSERT INTO opi_dbi_res_std_f (
1753             resource_id,
1754             organization_id,
1755             transaction_date,
1756             std_usage_qty,
1757             uom,
1758             std_usage_qty_g,
1759             std_usage_val_b,
1760             std_usage_val_g,
1761             std_usage_val_sg,
1762             job_id,
1763             job_type,
1764             assembly_item_id,
1765             department_id,
1766             source,
1767             creation_date,
1768             last_update_date,
1769             created_by,
1770             last_updated_by,
1771             last_update_login,
1772             program_id,
1773             program_login_id,
1774             program_application_id,
1775             request_id)
1776     SELECT  /*+ LEADING(CAL) */
1777             jobres.resource_id                      resource_id,
1778             jobitem.organization_id                 organization_id,
1779             jobitem.completion_date                 transaction_date,
1780             sum(DECODE( jobres.scale_type, 0, jobres.plan_rsrc_usage * jobitem.cost_alloc,
1781                         DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty))                                      std_usage_qty,
1782             jobres.usage_uom                         uom,
1783    sum(DECODE( jobres.scale_type, 0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
1784                         DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty))                                    std_usage_qty_g,
1785             sum(DECODE(jobres.scale_type, 0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
1786                         DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty) * jobres_uom.std_factor / rescost_uom.std_factor * rescost.nominal_cost)
1787                                                     std_usage_val_b,
1788             sum(DECODE(jobres.scale_type,
1789                0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
1790                 DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
1791                ) * jobres_uom.std_factor / rescost_uom.std_factor * rescost.nominal_cost
1792                  * jobitem.conversion_rate)         std_usage_val_g,
1793             sum(DECODE(jobres.scale_type,
1794                0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
1795                 DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
1796                ) * jobres_uom.std_factor / rescost_uom.std_factor * rescost.nominal_cost
1797                  * jobitem.sec_conversion_rate)     std_usage_val_sg,
1798             jobitem.job_id                          job_id,
1799             jobitem.job_type                        job_type,
1800             jobitem.assembly_item_id                assembly_item_id,
1801             jobres.department_id                    department_id,
1802             jobitem.source                          source,
1803             sysdate,
1804             sysdate,
1805             g_user_id,
1806             g_user_id,
1807             g_login_id,
1808             g_program_id,
1809             g_program_login_id,
1810             g_program_application_id,
1811             g_request_id
1812     FROM
1813         (
1814             SELECT  job.organization_id,
1815                     job.assembly_item_id,
1816                     bmatl.plan_qty,
1817                     bmatl.actual_qty,
1818                     bmatl.cost_alloc,
1819                     job.job_id,
1820                     job.completion_date,
1821                     job.conversion_rate,
1822                     job.sec_conversion_rate,
1823                     job.job_type,
1824                     job.source
1825             FROM    opi_dbi_jobs_f job,
1826                     mtl_system_items_b msi,
1827                     gme_material_details bmatl
1828             WHERE   job.job_type = 4
1829             AND     job.std_res_flag = 1
1830             AND     bmatl.batch_id = job.job_id
1831             AND     bmatl.line_type = 1                    -- coproducts
1832             AND     msi.inventory_item_id = job.assembly_item_id
1833             AND     msi.organization_id = job.organization_id
1834             AND     bmatl.inventory_item_id = msi.inventory_item_id
1835         ) jobitem,
1836         (
1837             SELECT
1838                     job.job_id,
1839                     job.assembly_item_id,
1840                     bres.scale_type,
1841                     resdtl.usage_uom,
1842                     resdtl.resource_id,
1843                     resdtl.organization_id,
1844                     resdtl.resources,
1845                     resmst.resource_class department_id,
1846                     bres.plan_rsrc_usage * bresuom.std_factor / ruom.std_factor  plan_rsrc_usage,
1847                     bres.plan_rsrc_usage * bresuom.std_factor / hruom.std_factor plan_rsrc_usage_g,
1848                     pol.cost_type_id,
1849                     cmm.default_lot_cost_type_id,
1850                     pol.legal_entity_id
1851             FROM    opi_dbi_jobs_f job,
1852                     gme_batch_header bhdr,
1853                     gme_batch_steps bstep,
1854                     gme_batch_step_resources bres,
1855                     cr_rsrc_dtl resdtl,
1856                     cr_rsrc_mst_b resmst,
1857                     gmf_fiscal_policies pol,
1858                     sy_uoms_mst_v bresuom,
1859                     sy_uoms_mst_v ruom,
1860                     sy_uoms_mst_v hruom,
1861                     org_organization_definitions org_def,
1862                     cm_mthd_mst cmm
1863             WHERE
1864                     job.std_res_flag = 1
1865             AND     job.job_type = 4
1866             AND     bhdr.batch_id = job.job_id
1867             AND     bstep.batch_id = job.job_id
1868             AND     bres.batchstep_id = bstep.batchstep_id
1869             AND     resdtl.organization_id= bhdr.organization_id
1870             AND     resdtl.resources = bres.resources
1871             AND     resmst.resources = resdtl.resources
1872             AND     bresuom.uom_code = bres.usage_um
1873             AND     ruom.uom_code = resdtl.usage_uom
1874             AND     hruom.uom_code = g_hr_uom
1875             AND     bhdr.organization_id = org_def.organization_id
1876             AND     org_def.legal_entity = pol.legal_entity_id
1877             AND     pol.cost_type_id = cmm.cost_type_id
1878         ) jobres,
1879          (
1880             SELECT  period.cost_type_id,
1881                     period.legal_entity_id,
1882                     period.period_id,
1883                     period.start_date,
1884                     period.end_date
1885             FROM    gmf_period_statuses period
1886             WHERE   period.end_date >= g_global_start_date
1887             AND     period.start_date <= sysdate
1888             ) cal,
1889         cm_rsrc_dtl     rescost,
1890         sy_uoms_mst_v     jobres_uom,
1891         sy_uoms_mst_v     rescost_uom
1892     WHERE   jobres.job_id = jobitem.job_id -- combine all batch resources with all batch coproducts
1893     AND     jobres.assembly_item_id = jobitem.assembly_item_id
1894     AND     cal.cost_type_id in (jobres.cost_type_id, jobres.default_lot_cost_type_id)
1895     AND     cal.legal_entity_id = jobres.legal_entity_id
1896     AND     jobitem.completion_date BETWEEN cal.start_date AND cal.end_date
1897     AND     rescost.resources = jobres.resources
1898     AND     rescost.organization_id = jobres.organization_id
1899     AND     rescost.period_id = cal.period_id
1900     AND     rescost.cost_type_id = cal.cost_type_id
1901     AND     jobres_uom.uom_code = jobres.usage_uom
1902     AND     rescost_uom.uom_code = rescost.usage_uom
1903     GROUP BY
1904             jobitem.organization_id,
1905             jobres.department_id,
1906             jobitem.job_id,
1907             jobitem.job_type,
1908             jobitem.assembly_item_id,
1909             jobres.usage_uom,
1910             jobres.resource_id,
1911             jobitem.completion_date,
1912             jobitem.source;
1913 
1914     l_rowcount := SQL%ROWCOUNT;
1915 
1916     COMMIT;
1917 
1918      bis_collection_utilities.put_line('OPM resource std: ' ||
1919                l_rowcount || ' rows initially collected into fact table at ' ||
1920                To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1921 
1922     bis_collection_utilities.put_line('Exit initial_opm_res_std() ' ||
1923                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1924 
1925 EXCEPTION WHEN OTHERS THEN
1926 
1927     errbuf:= Sqlerrm;
1928     retcode:= SQLCODE;
1929 
1930     ROLLBACK;
1931     bis_collection_utilities.wrapup(p_status => FALSE,
1932                                     p_count => 0,
1933                                     p_message => 'Failed in initial_opm_res_std.');
1934 
1935     RAISE_APPLICATION_ERROR(-20000,errbuf);
1936 
1937 END initial_opm_res_std;
1938 
1939 
1940 /*======================================================
1941     This procedure extracts standard resource usage data
1942     into the staging table for incremental load.
1943 
1944     Parameters:
1945     - errbuf: error buffer
1946     - retcode: return code
1947 =======================================================*/
1948 PROCEDURE incremental_opm_res_std  (errbuf IN OUT NOCOPY varchar2,
1949                                     retcode in out NOCOPY VARCHAR2  ) IS
1950     l_stmt_num NUMBER;
1951     l_rowcount NUMBER;
1952 
1953 
1954 BEGIN
1955 
1956     bis_collection_utilities.put_line('Enter incremental_opm_res_std() ' ||
1957                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
1958 
1959     DELETE  opi_dbi_res_std_f std
1960     WHERE   (job_id, job_type)
1961     IN      (SELECT job_id,
1962                     job_type
1963             FROM    opi_dbi_jobs_f
1964             WHERE   std_res_flag = 1
1965             AND     job_type = 4); -- need to extract again
1966 
1967      INSERT INTO opi_dbi_res_std_f
1968         (resource_id,
1969         organization_id,
1970         transaction_date,
1971         std_usage_qty,
1972         uom,
1973         std_usage_qty_g,
1974         std_usage_val_b,
1975         std_usage_val_g,
1976         std_usage_val_sg,
1977         job_id,
1978         job_type,
1979         assembly_item_id,
1980         department_id,
1981         source,
1982         creation_date,
1983         last_update_date,
1984         created_by,
1985         last_updated_by,
1986         last_update_login,
1987         program_id,
1988         program_login_id,
1989         program_application_id,
1990         request_id)
1991     SELECT /*+ LEADING(CAL) */
1992         jobres.resource_id                       resource_id,
1993         jobitem.organization_id                  organization_id,
1994         jobitem.completion_date                  transaction_date,
1995         sum(DECODE(jobres.scale_type,
1996           0, jobres.plan_rsrc_usage * jobitem.cost_alloc,
1997            DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
1998           ))                                      std_usage_qty,
1999         jobres.usage_uom                          uom,
2000         sum(DECODE(jobres.scale_type,
2001           0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
2002            DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
2003           ))                                      std_usage_qty_g,
2004         sum(DECODE(jobres.scale_type,
2005                0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
2006             DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
2007                ) * jobres_uom.std_factor / rescost_uom.std_factor * rescost.nominal_cost)
2008                                                  std_usage_val_b,
2009         sum(DECODE(jobres.scale_type,
2010                0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
2011             DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
2012          ) * jobres_uom.std_factor / rescost_uom.std_factor * rescost.nominal_cost
2013                  * jobitem.conversion_rate)       std_usage_val_g,
2014         sum(DECODE(jobres.scale_type,
2015                0, jobres.plan_rsrc_usage_g * jobitem.cost_alloc,
2016              DECODE(jobitem.plan_qty,0,0,((jobres.plan_rsrc_usage_g * jobitem.cost_alloc) / jobitem.plan_qty)) * jobitem.actual_qty
2017                ) * jobres_uom.std_factor / rescost_uom.std_factor * rescost.nominal_cost
2018                  * jobitem.sec_conversion_rate)       std_usage_val_sg,
2019         jobitem.job_id                           job_id,
2020         jobitem.job_type                         job_type,
2021         jobitem.assembly_item_id                 assembly_item_id,
2022         jobres.department_id                     department_id,
2023         jobitem.source                           source,
2024         sysdate,
2025         sysdate,
2026         g_user_id,
2027         g_user_id,
2028         g_login_id,
2029         g_program_id,
2030         g_program_login_id,
2031         g_program_application_id,
2032         g_request_id
2033   FROM
2034         (
2035             SELECT
2036                 job.organization_id,
2037                 job.assembly_item_id,
2038                 bmatl.plan_qty,
2039                 bmatl.actual_qty,
2040                 bmatl.cost_alloc,
2041                 job.job_id,
2042                 job.completion_date,
2043                 job.conversion_rate,
2044                 job.sec_conversion_rate,
2045                 job.job_type,
2046                 job.source
2047             FROM
2048                 opi_dbi_jobs_f job,
2049                 mtl_system_items_b msi,
2050                 gme_material_details bmatl
2051             WHERE
2052                 job.job_type = 4
2053             AND job.std_res_flag = 1
2054             AND bmatl.batch_id = job.job_id
2055             AND bmatl.line_type = 1                    -- coproducts
2056             AND msi.inventory_item_id = job.assembly_item_id
2057             AND msi.organization_id = job.organization_id
2058             AND bmatl.inventory_item_id = msi.inventory_item_id
2059         ) jobitem,
2060         (
2061             SELECT
2062                 job.job_id,
2063                 job.assembly_item_id,
2064                 bres.scale_type,
2065                 resdtl.usage_uom,
2066                 resdtl.resource_id,
2067                 resdtl.organization_id,
2068                 resdtl.resources,
2069                 resmst.resource_class department_id,
2070                 bres.plan_rsrc_usage * bresuom.std_factor / ruom.std_factor  plan_rsrc_usage,
2071                 bres.plan_rsrc_usage * bresuom.std_factor / hruom.std_factor plan_rsrc_usage_g,
2072                 pol.cost_type_id,
2073                 cmm.default_lot_cost_type_id,
2074                 pol.legal_entity_id
2075             FROM
2076                 opi_dbi_jobs_f job,
2077                 gme_batch_header bhdr,
2078                 gme_batch_steps bstep,
2079                 gme_batch_step_resources bres,
2080                 cr_rsrc_dtl resdtl,
2081                 cr_rsrc_mst_b resmst,
2082                 gmf_fiscal_policies pol,
2083                 sy_uoms_mst_v bresuom,
2084                 sy_uoms_mst_v ruom,
2085                 sy_uoms_mst_v hruom,
2086                 org_organization_definitions org_def,
2087                 cm_mthd_mst cmm
2088             WHERE
2089                 job.std_res_flag = 1
2090             AND job.job_type = 4
2091             AND bhdr.batch_id = job.job_id
2092             AND bstep.batch_id = job.job_id
2093             AND bres.batchstep_id = bstep.batchstep_id
2094             AND resdtl.organization_id = bhdr.organization_id
2095             AND resdtl.resources = bres.resources
2096             AND resmst.resources = resdtl.resources
2097             AND bresuom.uom_code = bres.usage_um
2098             AND ruom.uom_code = resdtl.usage_uom
2099             AND hruom.uom_code = g_hr_uom
2100             AND bhdr.organization_id = org_def.organization_id
2101             AND org_def.legal_entity = pol.legal_entity_id
2102             AND pol.cost_type_id = cmm.cost_type_id
2103         ) jobres,
2104         (
2105             SELECT  period.cost_type_id,
2106                     period.legal_entity_id,
2107                     period.period_id,
2108                     period.start_date,
2109                     period.end_date
2110             FROM    gmf_period_statuses period
2111             WHERE   period.end_date >= g_global_start_date
2112             AND     period.start_date <= sysdate
2113             ) cal,
2114         cm_rsrc_dtl rescost,
2115         sy_uoms_mst_v jobres_uom,
2116         sy_uoms_mst_v rescost_uom
2117     WHERE
2118         jobres.job_id = jobitem.job_id -- combine all batch resources with all batch coproducts
2119     AND jobres.assembly_item_id = jobitem.assembly_item_id
2120     AND cal.cost_type_id in (jobres.cost_type_id, jobres.default_lot_cost_type_id)
2121     AND cal.legal_entity_id = jobres.legal_entity_id
2122     AND jobitem.completion_date BETWEEN cal.start_date AND cal.end_date
2123     AND rescost.resources = jobres.resources
2124     AND rescost.organization_id = jobres.organization_id
2125     AND rescost.period_id = cal.period_id
2126     AND rescost.cost_type_id = cal.cost_type_id
2127     AND jobres_uom.uom_code = jobres.usage_uom
2128     AND rescost_uom.uom_code = rescost.usage_uom
2129     GROUP BY
2130        jobitem.organization_id,
2131        jobres.department_id,
2132        jobitem.job_id,
2133        jobitem.job_type,
2134        jobitem.assembly_item_id,
2135        jobres.usage_uom,
2136        jobres.resource_id,
2137        jobitem.completion_date,
2138        jobitem.source;
2139 
2140     l_rowcount := sql%rowcount;
2141 
2142     bis_collection_utilities.put_line('OPM resource std: ' ||
2143                l_rowcount || ' rows incrementally collected into staging table at ' ||
2144                to_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2145 
2146     bis_collection_utilities.put_line('Exit incremental_opm_res_std() ' ||
2147                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2148 
2149 EXCEPTION WHEN OTHERS THEN
2150 --{
2151     errbuf:= Sqlerrm;
2152     retcode:= SQLCODE;
2153 
2154     ROLLBACK;
2155     bis_collection_utilities.wrapup(p_status => FALSE,
2156                    p_count => 0,
2157                    p_message => 'Failed in incremental_opm_res_std.'
2158                    );
2159 
2160     RAISE_APPLICATION_ERROR(-20000,errbuf);
2161 --}
2162 END incremental_opm_res_std;
2163 
2164 
2165 
2166 /*======================================================================
2167     This is the wrapper procedure for Resource initial load which extracts
2168     actual resource usage and resource availability data for discrete
2169     and process organizations.
2170 
2171     Parameters:
2172     - errbuf: error buffer
2173     - retcode: return code
2174     - p_degree: degree
2175 =======================================================================*/
2176 
2177 PROCEDURE initial_load_res_utl (errbuf  IN OUT NOCOPY VARCHAR2,
2178                                 retcode IN OUT NOCOPY VARCHAR2,
2179                                 p_degree       NUMBER     ) IS
2180     l_stmt_num NUMBER;
2181     l_row_count NUMBER;
2182     l_err_num NUMBER;
2183     l_err_msg VARCHAR2(255);
2184     l_error_flag  BOOLEAN;
2185 
2186     l_opi_schema      VARCHAR2(30);
2187     l_status          VARCHAR2(30);
2188     l_industry        VARCHAR2(30);
2189 
2190     l_comm_opi_avail_flag   BOOLEAN;
2191     l_comm_opm_avail_flag   BOOLEAN;
2192     l_comm_opi_actual_flag   BOOLEAN;
2193     l_comm_opm_actual_flag   BOOLEAN;
2194 
2195     l_opi_start_date    DATE;
2196     l_opi_end_date      DATE;
2197 
2198     l_opm_start_date    opi_dbi_run_log_curr.from_bound_date%type;
2199     l_opm_end_date      opi_dbi_run_log_curr.to_bound_date%type;
2200 
2201     l_r12_mgr_date      opi_dbi_conc_prog_run_log.last_run_date%type;
2202 
2203     SCHEMA_INFO_NOT_FOUND   exception;
2204 BEGIN
2205 
2206     -- initialization block
2207     l_error_flag := FALSE;
2208     l_comm_opi_avail_flag := FALSE;
2209     l_comm_opm_avail_flag := FALSE;
2210     l_comm_opi_actual_flag := FALSE;
2211     l_comm_opm_actual_flag := FALSE;
2212 
2213     IF BIS_COLLECTION_UTILITIES.SETUP( 'OPI_DBI_RES_AVAIL_F' ) = false then
2214     --{
2215         RAISE_APPLICATION_ERROR(-20000, errbuf);
2216     --}
2217     END IF;
2218 
2219     -- Performance tuning change
2220     execute immediate 'alter session set hash_area_size=100000000 ';
2221     execute immediate 'alter session set sort_area_size=100000000 ';
2222 
2223     bis_collection_utilities.put_line('Initial Load starts at  '
2224                      || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2225 
2226     -- setup globals
2227     bis_collection_utilities.put_line('Setup Global Parameters ....');
2228     l_stmt_num :=10;
2229     check_setup_globals(errbuf => errbuf, retcode => retcode);
2230 
2231     IF retcode <> 0 THEN
2232     --{
2233         RETURN ;
2234     --}
2235     END IF;
2236 
2237      -- common clean up
2238     l_stmt_num := 20;
2239 
2240     IF fnd_installation.get_app_info( 'OPI', l_status, l_industry, l_opi_schema) THEN
2241     --{
2242         execute immediate 'truncate table ' || l_opi_schema
2243         || '.opi_dbi_res_conv_rates ';
2244 
2245         execute immediate 'truncate table ' || l_opi_schema
2246         || '.opi_dbi_res_avail_stg ';
2247 
2248         execute immediate 'truncate table ' || l_opi_schema
2249         || '.opi_dbi_res_actual_stg ';
2250 
2251         execute immediate 'truncate table ' || l_opi_schema
2252         || '.opi_dbi_res_avail_f PURGE MATERIALIZED VIEW LOG  ';
2253 
2254          execute immediate 'truncate table ' || l_opi_schema
2255         || '.opi_dbi_res_actual_f PURGE MATERIALIZED VIEW LOG ';
2256     --}
2257     ELSE
2258     --{
2259         RAISE SCHEMA_INFO_NOT_FOUND;
2260     --}
2261     END IF;
2262 
2263 
2264     /*** Collect Actual Resource Usage Data ***/
2265 
2266     -- Load discrete actual data to Staging table
2267     bis_collection_utilities.put_line('Load discrete resource actual into staging ...');
2268 
2269     l_stmt_num := 30;
2270     initial_opi_res_actual(errbuf => errbuf, retcode => retcode);
2271 
2272     IF retcode <> 0 THEN
2273     --{
2274         l_error_flag := TRUE;
2275     --}
2276     END IF;
2277 
2278     -- Get R12 migration date.  If GSD < R12 migration date,
2279     -- get OPM data from Pre R12 data model
2280 
2281     BEGIN
2282         SELECT  last_run_date
2283         INTO    l_r12_mgr_date
2284         FROM    opi_dbi_conc_prog_run_log
2285         WHERE   etl_type = 'R12_MIGRATION';
2286     EXCEPTION
2287         WHEN NO_DATA_FOUND THEN
2288         --{
2289             l_r12_mgr_date := g_global_start_date;
2290         --}
2291     END;
2292 
2293     IF (g_global_start_date < l_r12_mgr_date) THEN
2294     --{
2295         bis_collection_utilities.put_line('Load process pre-r12 resource actual into staging ... ');
2296         opi_dbi_pre_r12_res_pkg.pre_r12_opm_res_actual(errbuf => errbuf, retcode => retcode);
2297     --}
2298     END IF;
2299 
2300     -- get OPM data from R12 data model
2301     l_stmt_num := 35;
2302 
2303     -- Call API to load ledger data into Global temp table
2304     -- This temp table will be joined to extract process adjustments
2305     bis_collection_utilities.put_line('Loading Ledger data into temp table');
2306     opi_dbi_bounds_pkg.load_opm_org_ledger_data;
2307 
2308     -- Committing the data. Since the temp table is made with On Commit preserve rows
2309     -- there will be no problem.
2310     commit;
2311 
2312     l_stmt_num := 40;
2313     bis_collection_utilities.put_line('Load process resource actual into staging ... ');
2314     initial_opm_res_actual(errbuf => errbuf, retcode => retcode);
2315 
2316     IF retcode <> 0 THEN
2317     --{
2318         l_error_flag := TRUE;
2319     --}
2320     END IF;
2321 
2322 
2323     /*** Collect Resource Availability Data ***/
2324 
2325     -- Get discrete and process availability date bounds
2326     l_stmt_num := 50;
2327 
2328 
2329     BEGIN
2330         SELECT  trunc(from_bound_date), trunc(to_bound_date)
2331         INTO    l_opi_start_date, l_opi_end_date
2332         FROM    opi_dbi_run_log_curr
2333         WHERE   etl_id = RESOURCE_VAR_ETL
2334         AND     source = OPI_SOURCE;
2335 
2336     EXCEPTION
2337         WHEN NO_DATA_FOUND THEN
2338         --{
2339             RAISE NO_DATA_FOUND;
2340         --}
2341     END;
2342 
2343     BEGIN
2344         SELECT  trunc(from_bound_date), trunc(to_bound_date)
2345         INTO    l_opm_start_date, l_opm_end_date
2346         FROM    opi_dbi_run_log_curr
2347         WHERE   etl_id = RESOURCE_VAR_ETL
2348         AND     source = OPM_SOURCE;
2349 
2350     EXCEPTION
2351         WHEN NO_DATA_FOUND THEN
2352         --{
2353             RAISE NO_DATA_FOUND;
2354         --}
2355     END;
2356 
2357 
2358     -- Load discrete availability data into Staging table
2359     bis_collection_utilities.put_line('Load discrete res avail into staging ');
2360 
2361      l_stmt_num := 60;
2362     initial_opi_res_avail(p_start_date => l_opi_start_date,
2363                           p_end_date => l_opi_end_date,
2364                           errbuf => errbuf,
2365                           retcode => retcode);
2366 
2367     IF retcode <> 0 THEN
2368     --{
2369         l_error_flag := TRUE;
2370     --}
2371     END IF;
2372 
2373 
2374     -- Load process availability data into Staging table
2375     bis_collection_utilities.put_line('Load process res avail into staging ');
2376 
2377     l_stmt_num := 70;
2378     initial_opm_res_avail(p_start_date => l_opm_start_date,
2379                           p_end_date => l_opm_end_date,
2380                           errbuf => errbuf,
2381                           retcode => retcode);
2382 
2383     IF retcode <> 0 THEN
2384     --{
2385         l_error_flag := TRUE;
2386     --}
2387     END IF;
2388 
2389 
2390     -- For improve perf, need to commit in stg/conversion rate tables
2391     -- and gather statistics
2392     commit;
2393 
2394     gather_stats(p_table_name => 'OPI_DBI_RES_ACTUAL_STG');
2395 
2396     gather_stats(p_table_name => 'OPI_DBI_RES_AVAIL_STG');
2397 
2398     get_res_conversion_rate(errbuf => errbuf, retcode => retcode );
2399 
2400     commit;
2401 
2402     --gather_stats(p_table_name => 'OPI_DBI_RES_CONV_RATES');
2403 
2404 
2405     IF l_error_flag <> TRUE THEN
2406     --{
2407         -- load Actual data into Fact
2408         l_stmt_num := 80;
2409 
2410         bis_collection_utilities.put_line('Initially load actual data from staging to actual fact ...');
2411 
2412         INSERT /*+ append parallel(c) */
2413         INTO opi_dbi_res_actual_f c (
2414             resource_id,
2415             department_id,
2416             organization_id,
2417             uom,
2418             actual_qty_draft,
2419             actual_qty,
2420             actual_qty_g_draft,
2421             actual_qty_g,
2422             actual_val_b_draft,
2423             actual_val_b,
2424             actual_val_g,
2425             actual_val_sg,
2426             job_id,
2427             job_type,
2428             assembly_item_id,
2429             source,
2430             creation_date,
2431             last_update_date,
2432             created_by,
2433             last_updated_by,
2434             last_update_login,
2435             program_id,
2436             program_login_id,
2437             program_application_id,
2438             request_id )
2439         SELECT   /*+ use_hash(stg) parallel(stg)
2440                      use_hash(rate) parallel(rate) */
2441             stg.resource_id,
2442             stg.department_id,
2443             stg.organization_id,
2444             stg.uom,
2445             sum (stg.actual_qty_draft)                      actual_qty_draft,
2446             sum (stg.actual_qty_draft + stg.actual_qty)     actual_qty,
2447             sum (stg.actual_qty_g_draft)                    actual_qty_g_draft,
2448             sum (stg.actual_qty_g_draft + stg.actual_qty_g) actual_qty_g,
2449             sum (stg.actual_val_b_draft)                    actual_val_b_draft,
2450             sum (stg.actual_val_b_draft + stg.actual_val_b) actual_val_b,
2451             sum ((stg.actual_val_b_draft  + stg.actual_val_b)
2452                 * rate.conversion_rate)                     actual_val_g,
2453             sum ((stg.actual_val_b_draft + stg.actual_val_b)
2454                 * rate.sec_conversion_rate)                 actual_val_sg,
2455             stg.job_id,
2456             stg.job_type,
2457             stg.assembly_item_id,
2458             stg.source,
2459             sysdate,
2460             sysdate,
2461             g_user_id,
2462             g_user_id,
2463             g_login_id,
2464             g_program_id,
2465             g_program_login_id,
2466              g_program_application_id,
2467             g_request_id
2468         FROM
2469             opi_dbi_res_actual_stg      stg,
2470             opi_dbi_res_conv_rates rate
2471         WHERE
2472             stg.organization_id = rate.organization_id
2473         AND stg.transaction_date  = rate.transaction_date
2474         GROUP BY
2475                 stg.resource_id,
2476                 stg.department_id,
2477                 stg.organization_id,
2478                 stg.job_id,
2479                 stg.job_type,
2480                 stg.assembly_item_id,
2481                 stg.source,
2482                 stg.uom;
2483 
2484         l_row_count := sql%rowcount;
2485 
2486         bis_collection_utilities.put_line('Load res actual ' || l_row_count ||
2487                     ' rows into FACT '
2488                     || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2489      --}
2490     ELSE
2491     --{
2492         bis_collection_utilities.put_line('Failed to load res actual data to fact');
2493     -->
2494     END IF;
2495 
2496 
2497 
2498     -- Load Actual and Availability data in to Fact table
2499     IF l_error_flag <> TRUE THEN
2500     --{
2501         l_stmt_num := 90;
2502 
2503         bis_collection_utilities.put_line('Initially load actual and avail data from staging to avail fact ...');
2504 
2505         INSERT /*+ append parallel(b) */
2506         INTO opi_dbi_res_avail_f b (
2507                 resource_id,
2508                 department_id,
2509                 organization_id,
2510                 transaction_date,
2511                 uom,
2512                 avail_qty,
2513                 avail_qty_g,
2514                 avail_val_b,
2515                 avail_val_g,
2516                 avail_val_sg,
2517                 actual_qty_draft,
2518                 actual_qty,
2519                 actual_qty_g_draft,
2520                 actual_qty_g,
2521                 actual_val_b_draft,
2522                 actual_val_b,
2523                 actual_val_g,
2524                 actual_val_sg,
2525                 source,
2526                 creation_date,
2527                 last_update_date,
2528                 created_by,
2529                 last_updated_by,
2530                 last_update_login,
2531                 program_id,
2532                 program_login_id,
2533                 program_application_id,
2534                 request_id)
2535         SELECT  res.resource_id,
2536                 res.department_id,
2537                 res.organization_id,
2538                 res.transaction_date,
2539                 max (res.uom),
2540                 sum (res.avail_qty),
2541                 sum (res.avail_qty_g),
2542                 sum (res.avail_val_b),
2543                 sum (res.avail_val_g),
2544                 sum (res.avail_val_sg),
2545                 sum (res.actual_qty_draft),
2546                 sum (res.actual_qty),
2547                 sum (res.actual_qty_g_draft),
2548                 sum (res.actual_qty_g),
2549                 sum (res.actual_val_b_draft),
2550                 sum (res.actual_val_b),
2551                 sum (res.actual_val_g),
2552                 sum (res.actual_val_sg),
2553                 max (res.source),
2554                 sysdate,
2555                 sysdate,
2556                 g_user_id,
2557                 g_user_id,
2558                 g_login_id,
2559                 g_program_id,
2560                 g_program_login_id,
2561                 g_program_application_id,
2562                 g_request_id
2563         FROM
2564                 (SELECT  /*+ use_hash(stg) parallel(stg)
2565                          use_hash(rate) parallel(rate) */
2566                         stg.resource_id,
2567                         stg.department_id,
2568                         stg.organization_id,
2569                          stg.transaction_date,
2570                         MAX (stg.uom)   uom,
2571                         NULL avail_qty,
2572                         NULL avail_qty_g,
2573                         NULL avail_val_b,
2574                         NULL avail_val_g,
2575                         NULL avail_val_sg,
2576                         SUM (stg.actual_qty_draft)                      actual_qty_draft,
2577                         SUM (stg.actual_qty_draft + stg.actual_qty)     actual_qty,
2578                         SUM (stg.actual_qty_g_draft)                    actual_qty_g_draft,
2579                         SUM (stg.actual_qty_g_draft + stg.actual_qty_g) actual_qty_g,
2580                         SUM (stg.actual_val_b_draft)                    actual_val_b_draft,
2581                         SUM (stg.actual_val_b_draft + stg.actual_val_b) actual_val_b,
2582                         SUM ((stg.actual_val_b_draft + stg.actual_val_b)
2583                             * rate.conversion_rate)                     actual_val_g,
2584                         sum ((stg.actual_val_b_draft + stg.actual_val_b)
2585                             * rate.sec_conversion_rate)                 actual_val_sg,
2586                         MAX (stg.source) source
2587                 FROM    opi_dbi_res_actual_stg stg,
2588                         opi_dbi_res_conv_rates rate
2589                 WHERE   stg.organization_id = rate.organization_id
2590                 AND     stg.transaction_date  = rate.transaction_date
2591                 GROUP BY
2592                         stg.resource_id,
2593                         stg.department_id,
2594                         stg.organization_id,
2595                         stg.transaction_date
2596                 UNION ALL
2597                 SELECT /*+ use_hash(stg) parallel(stg)
2598                         use_hash(rate) parallel(rate) */
2599                         stg.resource_id,
2600                         stg.department_id,
2601                         stg.organization_id,
2602                         stg.transaction_date,
2603                         stg.uom,
2604                         stg.avail_qty,
2605                         stg.avail_qty_g,
2606                         stg.avail_val_b,
2607                         stg.avail_val_b * rate.conversion_rate avail_val_g,
2608                         stg.avail_val_b * rate.sec_conversion_rate avail_val_sg,
2609                         NULL actual_qty_draft,
2610                         NULL actual_qty,
2611                         NULL actual_qty_g_draft,
2612                         NULL actual_qty_g,
2613                         NULL actual_val_b_draft,
2614                         NULL actual_val_b,
2615                         NULL actual_val_g,
2616                         NULL actual_val_sg,
2617                         stg.source
2618                  FROM   opi_dbi_res_avail_stg stg,
2619                         opi_dbi_res_conv_rates rate
2620                 WHERE   stg.organization_id = rate.organization_id
2621                 AND     stg.transaction_date  = rate.transaction_date
2622                 ) res
2623           GROUP BY
2624                 res.resource_id,
2625                 res.department_id,
2626                 res.organization_id,
2627                 res.transaction_date;
2628 
2629         l_row_count := SQL%rowcount;
2630         bis_collection_utilities.put_line('Load res avail into FACT ' ||
2631                 l_row_count || ' rows, completed at '
2632                 || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2633 
2634 
2635         -- update common modules for OPI
2636         l_comm_opi_avail_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => RESOURCE_VAR_ETL,
2637                                                                                 p_source => 1);
2638         l_comm_opm_avail_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => RESOURCE_VAR_ETL,
2639                                                                                 p_source => 2);
2640 
2641         l_comm_opi_actual_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => ACTUAL_RES_ETL,
2642                                                                                  p_source => 1);
2643         l_comm_opm_actual_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => ACTUAL_RES_ETL,
2644                                                                                  p_source => 2);
2645 
2646         IF l_comm_opi_avail_flag AND l_comm_opm_avail_flag
2647             AND l_comm_opi_actual_flag AND l_comm_opm_actual_flag THEN
2648         --{
2649             COMMIT;
2650 
2651             execute immediate 'truncate table ' || l_opi_schema
2652                               || '.opi_dbi_res_conv_rates ';
2653 
2654             execute immediate 'truncate table ' || l_opi_schema
2655                               || '.opi_dbi_res_avail_stg ';
2656 
2657             execute immediate 'truncate table ' || l_opi_schema
2658                               || '.opi_dbi_res_actual_stg ';
2659 
2660             bis_collection_utilities.WRAPUP(p_status => TRUE,
2661                                             p_count => l_row_count,
2662                                             p_message => 'successful in initial_load_res_utl.');
2663         --}
2664         ELSE
2665         --{
2666             retcode := g_error ;
2667             errbuf  := 'Error in report to common modules. Please check log file for details.';
2668 
2669             rollback;
2670 
2671             bis_collection_utilities.put_line('Error in initial_load_res_utl at ' || l_stmt_num);
2672             bis_collection_utilities.wrapup(p_status => FALSE,
2673                  p_count => 0,
2674                    p_message => 'failed in initial_load_res_utl.'
2675                    );
2676         --}
2677         END IF;
2678     ELSE
2679     --{
2680         rollback;
2681         retcode := g_error ;
2682         errbuf  := 'Please check log file for details.';
2683         bis_collection_utilities.put_line('Error in initial_load_res_utl at ' || l_stmt_num);
2684         bis_collection_utilities.wrapup(p_status => FALSE,
2685                    p_count => 0,
2686                    p_message => 'failed in initial_load_res_utl.');
2687     --}
2688     END IF;
2689 
2690     bis_collection_utilities.put_line('Exit initial_load_res_utl() ' ||
2691                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2692 
2693 
2694 EXCEPTION
2695 --{
2696     WHEN SCHEMA_INFO_NOT_FOUND THEN
2697     --{
2698         bis_collection_utilities.put_line('Schema information was not found.');
2699     --}
2700     WHEN OTHERS THEN
2701     --{
2702     Errbuf:= Sqlerrm;
2703     Retcode:= SQLCODE;
2704     ROLLBACK;
2705     bis_collection_utilities.put_line('Error in initial_load_res_utl at ' || l_stmt_num);
2706     bis_collection_utilities.wrapup(p_status => FALSE,
2707                    p_count => 0,
2708                    p_message => 'failed in initial_load_res_utl.'
2709                    );
2710 
2711     RAISE_APPLICATION_ERROR(-20000,errbuf);
2712     --}
2713 --}
2714 END initial_load_res_utl;
2715 
2716 
2717 /*======================================================================
2718     This is the incremental procedure to extract resource standard usage
2719     data for discrete organizations.
2720 
2721     Parameters:
2722     - errbuf: error buffer
2723     - retcode: return code
2724 =======================================================================*/
2725 
2726 PROCEDURE incremental_opi_res_std (errbuf   IN OUT NOCOPY VARCHAR2,
2727                                    retcode  IN OUT NOCOPY VARCHAR2  ) IS
2728     l_count number;
2729 
2730 BEGIN
2731 
2732     bis_collection_utilities.put_line('Enter incremental_opi_res_std() ' ||
2733                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2734 
2735     retcode := 0;
2736 
2737     DELETE  opi_dbi_res_std_f std
2738     WHERE   (job_id, job_type)
2739     IN      (SELECT job_id,
2740                     job_type
2741             FROM    opi_dbi_jobs_f
2742             WHERE   std_res_flag = 1 -- need to extract again
2743             AND     source = OPI_SOURCE);
2744 
2745     INSERT INTO opi_dbi_res_std_f (
2746         resource_id,
2747         department_id,
2748         organization_id,
2749         transaction_date,
2750         uom,
2751         std_usage_qty,
2752         std_usage_qty_g,
2753         std_usage_val_b,
2754         std_usage_val_g,
2755         std_usage_val_sg,
2756         job_id,
2757         job_type,
2758         assembly_item_id,
2759         source,
2760         creation_date,
2761         last_update_date,
2762         created_by,
2763         last_updated_by,
2764         last_update_login,
2765         program_id,
2766         program_login_id,
2767         program_application_id,
2768         request_id)
2769     SELECT
2770         wor.resource_id,
2771         nvl(bdr.share_from_dept_id, wo.department_id),
2772         job.organization_id,
2773         trunc (job.completion_date) transaction_date,
2774         br.unit_of_measure uom,
2775         SUM (Decode (basis_type,
2776                      1, wor.usage_rate_or_amount * job.actual_qty_completed,
2777                       2, wor.usage_rate_or_amount ) )  std_usage_qty,
2778         SUM (Decode (basis_type,
2779                      1, wor.usage_rate_or_amount * job.actual_qty_completed,
2780                      2, wor.usage_rate_or_amount )/
2781             m.conversion_rate * m2.conversion_rate ) std_usage_qty_g,
2782         SUM (Decode (basis_type,
2783                      1, wor.usage_rate_or_amount * job.actual_qty_completed,
2784                      2, wor.usage_rate_or_amount ) * crc.resource_rate )
2785             std_usage_val_b,
2786         SUM (Decode (basis_type,
2787                      1, wor.usage_rate_or_amount * job.actual_qty_completed,
2788                      2, wor.usage_rate_or_amount ) * crc.resource_rate *
2789             job.conversion_rate )  std_usage_val_g,
2790         SUM (Decode (basis_type,
2791                      1, wor.usage_rate_or_amount * job.actual_qty_completed,
2792                      2, wor.usage_rate_or_amount ) * crc.resource_rate *
2793             job.sec_conversion_rate )  std_usage_val_sg,
2794         job.job_id,
2795         job.job_type,
2796         job.assembly_item_id,
2797         OPI_SOURCE source,
2798         sysdate,
2799         sysdate,
2800         g_user_id,
2801         g_user_id,
2802         g_login_id,
2803         g_program_id,
2804         g_program_login_id,
2805         g_program_application_id,
2806         g_request_id
2807       FROM  wip_operation_resources wor,
2808             wip_operations wo,
2809             opi_dbi_jobs_f job,
2810             bom_resources br,
2811             mtl_parameters mp,
2812             mtl_uom_conversions m,
2813             mtl_uom_conversions m2,
2814             cst_resource_costs crc,
2815             bom_department_resources bdr
2816       WHERE job.job_type IN (1,2,5) -- Discrete and Repetitive also OSFM
2817         AND job.std_res_flag = 1
2818         AND job.source = 1
2819         AND wor.organization_id = job.organization_id
2820         AND job.job_id = Nvl(wor.repetitive_schedule_id, wor.wip_entity_id)
2821         AND br.resource_id = wor.resource_id
2822         AND wo.organization_id = wor.organization_id
2823         AND wo.wip_entity_id = wor.wip_entity_id
2824         AND wo.operation_seq_num = wor.operation_seq_num
2825         AND nvl (wo.repetitive_schedule_id, -999) =
2826                     nvl (wor.repetitive_schedule_id, -999)
2827         AND m.inventory_item_id = 0
2828         AND m.uom_code = g_hr_uom
2829          AND m2.uom_code          = br.unit_of_measure
2830         AND m2.uom_class         = m.uom_class
2831         AND m2.inventory_item_id  = 0
2832         AND mp.organization_id   = wor.organization_id
2833         AND crc.resource_id      = br.resource_id
2834         AND crc.organization_id  = mp.organization_id
2835         AND bdr.resource_id      = wor.resource_id
2836         AND bdr.department_id    = wo.department_id
2837         AND (   (mp.primary_cost_method = 1 AND crc.cost_type_id = 1)
2838              OR (mp.primary_cost_method in (2,5,6) AND crc.cost_type_id =
2839                         mp.AVG_RATES_COST_TYPE_ID ) )
2840       GROUP BY
2841             job.organization_id,
2842             nvl(bdr.share_from_dept_id,wo.department_id),
2843             job.job_id,
2844             job.job_type,
2845             job.assembly_item_id,
2846             br.unit_of_measure,
2847             wor.resource_id,
2848             trunc(job.completion_date);
2849 
2850 
2851     l_count := sql%rowcount;
2852 
2853     bis_collection_utilities.put_line('Load OPI res std into FACT ' ||
2854                 l_count || ' rows, completed at '
2855                 || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2856 
2857     bis_collection_utilities.put_line('Exit incremental_opi_res_std() ' ||
2858                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2859 
2860 EXCEPTION WHEN OTHERS THEN
2861 --{
2862     Errbuf:= Sqlerrm;
2863     Retcode:= SQLCODE;
2864 
2865     bis_collection_utilities.put_line('Exception in incremental_opi_res_std ' || sqlerrm );
2866 --}
2867 END incremental_opi_res_std;
2868 
2869 
2870 /*======================================================================
2871     This is the wrapper procedure for Resource incremental load which extracts
2872     actual resource usage, resource availability, and resource standare usage
2873     data for discrete and process organizations.
2874 
2875     Parameters:
2876     - errbuf: error buffer
2877     - retcode: return code
2878 =======================================================================*/
2879 
2880 PROCEDURE incremental_load_res_utl (errbuf  IN OUT NOCOPY VARCHAR2,
2881                                     retcode IN OUT NOCOPY VARCHAR2 ) IS
2882     l_stmt_num NUMBER;
2883     l_row_count NUMBER;
2884     l_err_num NUMBER;
2885     l_err_msg VARCHAR2(255);
2886     l_error_flag  BOOLEAN;
2887 
2888     l_opi_schema      VARCHAR2(30);
2889     l_status          VARCHAR2(30);
2890     l_industry        VARCHAR2(30);
2891 
2892     l_last_collection_date DATE;
2893     l_comm_opi_avail_flag   BOOLEAN;
2894     l_comm_opm_avail_flag   BOOLEAN;
2895     l_comm_opi_actual_flag   BOOLEAN;
2896     l_comm_opm_actual_flag   BOOLEAN;
2897 
2898     l_count number;
2899 
2900     l_opi_start_date    DATE;
2901     l_opi_end_date      DATE;
2902 
2903     l_opm_start_date    opi_dbi_run_log_curr.from_bound_date%type;
2904     l_opm_end_date      opi_dbi_run_log_curr.to_bound_date%type;
2905 
2906     SCHEMA_INFO_NOT_FOUND   exception;
2907     NO_DATA_FOUND           exception;
2908 
2909 BEGIN
2910 
2911     bis_collection_utilities.put_line('Enter incremental_load_res_utl() ' ||
2912                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
2913 
2914     -- initialization block
2915     l_error_flag := FALSE;
2916     l_comm_opi_avail_flag := FALSE;
2917     l_comm_opm_avail_flag := FALSE;
2918     l_comm_opi_actual_flag := FALSE;
2919     l_comm_opm_actual_flag := FALSE;
2920 
2921 
2922     IF bis_collection_utilities.setup( 'OPI_DBI_RES_AVAIL_F' ) = false THEN
2923     --{
2924         RAISE_APPLICATION_ERROR(-20000, errbuf);
2925     --}
2926     END IF;
2927 
2928 
2929     -- setup globals
2930     bis_collection_utilities.put_line('Setup global parameters ...');
2931 
2932     l_stmt_num := 10;
2933 
2934     check_setup_globals(errbuf => errbuf, retcode => retcode);
2935 
2936     IF retcode <> 0 THEN
2937     --{
2938         RETURN ;
2939     --}
2940     END IF;
2941 
2942     -- Found this issue with the code during secondary currency fix UT.
2943     -- The conversion rates table is not cleaned up if the incremental
2944     -- load errors out. As a result, it starts accumulating duplicate rows.
2945     -- The worst case is when the program errors out due to missing rates,
2946     -- because then some of the rates in the table are actually the
2947     -- negative error codes returned by the FII API.
2948 
2949 
2950     l_stmt_num := 20;
2951     -- conversion rate table cleanup
2952     IF fnd_installation.get_app_info( 'OPI', l_status, l_industry, l_opi_schema) THEN
2953     --{
2954 
2955         execute immediate 'truncate table ' || l_opi_schema
2956          || '.opi_dbi_res_conv_rates ';
2957     --}
2958     ELSE
2959     --{
2960         retcode := g_error;
2961         RAISE SCHEMA_INFO_NOT_FOUND;
2962     --}
2963     END IF;
2964 
2965 
2966     /*** Collect Standard Resource Usage ***/
2967 
2968     -- Incrementally load resource standard usage fact for discrete
2969     bis_collection_utilities.put_line('Load discrete resource std into staging ...');
2970     l_stmt_num := 30;
2971 
2972     incremental_opi_res_std(errbuf => errbuf, retcode => retcode);
2973 
2974     IF retcode <> 0 THEN
2975     --{
2976         l_error_flag := TRUE;
2977     --}
2978     END IF;
2979 
2980 
2981     -- Incrementally load resource standard usage fact for process
2982     bis_collection_utilities.put_line('Load process resource std into staging ...');
2983     l_stmt_num := 40;
2984 
2985     incremental_opm_res_std(errbuf => errbuf, retcode => retcode);
2986 
2987      IF retcode <> 0 THEN
2988     --{
2989         l_error_flag := TRUE;
2990     --}
2991     END IF;
2992 
2993      --  update Job master's flag, for source 2
2994     UPDATE  opi_dbi_jobs_f
2995     SET     std_res_flag = 0,
2996             last_update_date = sysdate,
2997             last_updated_by = g_user_id,
2998             last_update_login = g_login_id
2999     WHERE   std_res_flag = 1;
3000 
3001     l_stmt_num := 50;
3002 
3003 
3004 
3005     /*** Collect Actual Resource Usage ***/
3006 
3007     -- Load discrete resource actual data into Staging table
3008 
3009     bis_collection_utilities.put_line('Load discrete res actual into staging ... ');
3010     l_stmt_num := 60;
3011     incremental_opi_res_actual(errbuf => errbuf, retcode => retcode);
3012 
3013     IF retcode <> 0 THEN
3014     --{
3015         l_error_flag := TRUE;
3016     --}
3017     END IF;
3018 
3019 
3020 
3021     -- Load process resource actual data into Staging table
3022 
3023     l_stmt_num := 65;
3024 
3025     -- Call API to load ledger data into Global temp table
3026     -- This temp table will be joined to extract process adjustments
3027     bis_collection_utilities.put_line ('Loading Ledger data into temp table');
3028     opi_dbi_bounds_pkg.load_opm_org_ledger_data;
3029 
3030     -- Committing the data. Since the temp table is made with On Commit preserve rows
3031     -- there will be no problem.
3032     commit;
3033 
3034     bis_collection_utilities.put_line('Load process res actual into staging ... ');
3035     l_stmt_num := 70;
3036     incremental_opm_res_actual(errbuf => errbuf, retcode => retcode);
3037 
3038     IF retcode <> 0 THEN
3039     --{
3040         l_error_flag := TRUE;
3041     --}
3042     END IF;
3043 
3044 
3045     /*** Collect Resource Availability Data ***/
3046 
3047     -- Get discrete and process availability date bounds
3048     l_stmt_num := 80;
3049 
3050     BEGIN
3051         SELECT  trunc(from_bound_date), trunc(to_bound_date)
3052         INTO    l_opi_start_date, l_opi_end_date
3053         FROM    opi_dbi_run_log_curr
3054         WHERE   etl_id = RESOURCE_VAR_ETL
3055         AND     source = OPI_SOURCE;
3056 
3057     EXCEPTION
3058         WHEN NO_DATA_FOUND THEN
3059         --{
3060             RAISE NO_DATA_FOUND;
3061         --}
3062     END;
3063 
3064     BEGIN
3065         SELECT  trunc(from_bound_date), trunc(to_bound_date)
3066         INTO    l_opm_start_date, l_opm_end_date
3067         FROM    opi_dbi_run_log_curr
3068         WHERE   etl_id = RESOURCE_VAR_ETL
3069         AND     source = OPM_SOURCE;
3070 
3071     EXCEPTION
3072         WHEN NO_DATA_FOUND THEN
3073         --{
3074             RAISE NO_DATA_FOUND;
3075         --}
3076     END;
3077 
3078     -- If the resource ETL is run more than once on the same day, wipe off
3079     -- data for the current date and re-extract
3080     l_stmt_num := 90;
3081 
3082     IF (l_opi_start_date = l_opi_end_date) THEN
3083     --{
3084         UPDATE  opi_dbi_res_avail_f
3085         SET     avail_qty = NULL,
3086                 uom = NULL,
3087                 avail_qty_g = NULL,
3088                 avail_val_b = NULL,
3089                 avail_val_g = NULL,
3090                 avail_val_sg = NULL,
3091                 last_update_date    = sysdate,
3092                 last_updated_by     = g_user_id,
3093                 last_update_login   = g_login_id
3094         WHERE   transaction_date =  l_opi_start_date
3095         AND     source = OPI_SOURCE;
3096     --}
3097     END IF;
3098 
3099      -- Load discrete availability data into Staging table
3100     bis_collection_utilities.put_line('Load discrete res avail into staging ...  ');
3101      l_stmt_num := 100;
3102 
3103     incremental_opi_res_avail(p_start_date => l_opi_start_date,
3104                               p_end_date => l_opi_end_date,
3105                               errbuf => errbuf,
3106                               retcode => retcode);
3107 
3108     IF retcode <> 0 THEN
3109     --{
3110         l_error_flag := TRUE;
3111     --}
3112     END IF;
3113 
3114 
3115     -- Load process availability data into Staging table
3116     bis_collection_utilities.put_line('Load process res avail into staging ...  ');
3117     l_stmt_num := 110;
3118 
3119     incremental_opm_res_avail(p_start_date => l_opm_start_date,
3120                               p_end_date => l_opm_end_date,
3121                               errbuf => errbuf,
3122                               retcode => retcode);
3123 
3124     IF retcode <> 0 THEN
3125     --{
3126         l_error_flag := TRUE;
3127     --}
3128     END IF;
3129 
3130 
3131     -- For improve perf, need to commit in stg/conversion rate tables
3132     -- and gather statistics
3133     commit;
3134 
3135     gather_stats(p_table_name => 'OPI_DBI_RES_ACTUAL_STG');
3136 
3137     gather_stats(p_table_name => 'OPI_DBI_RES_AVAIL_STG');
3138 
3139     get_res_conversion_rate(errbuf => errbuf, retcode => retcode );
3140 
3141     commit;
3142 
3143     --gather_stats(p_table_name => 'OPI_DBI_RES_CONV_RATES');
3144 
3145 
3146 
3147     -- Incrementally load data into Actual Fact
3148     IF l_error_flag <> TRUE THEN
3149     --{
3150         bis_collection_utilities.put_line('Merge res actual from staging to actual fact ...');
3151         l_stmt_num := 120;
3152 
3153          MERGE INTO opi_dbi_res_actual_f f
3154         USING (
3155         SELECT
3156             stg.resource_id,
3157             stg.department_id,
3158             stg.organization_id,
3159             stg.uom,
3160             sum (stg.actual_qty_draft)      actual_qty_draft,
3161             sum (stg.actual_qty)            actual_qty,
3162             sum (stg.actual_qty_g_draft)    actual_qty_g_draft,
3163             sum (stg.actual_qty_g)          actual_qty_g,
3164             sum (stg.actual_val_b_draft)    actual_val_b_draft,
3165             sum (stg.actual_val_b)          actual_val_b,
3166             min(rate.conversion_rate)           conversion_rate,
3167             min(rate.sec_conversion_rate)       sec_conversion_rate,
3168             stg.job_id,
3169             stg.job_type,
3170             stg.assembly_item_id,
3171             stg.source
3172           FROM  opi_dbi_res_actual_stg stg,
3173                 opi_dbi_res_conv_rates rate
3174           WHERE stg.organization_id = rate.organization_id
3175           AND   stg.transaction_date  = rate.transaction_date
3176           GROUP BY
3177                 stg.resource_id,
3178                 stg.department_id,
3179                 stg.organization_id,
3180                 stg.uom,
3181                 stg.job_id,
3182                 stg.job_type,
3183                 stg.assembly_item_id,
3184                 stg.source
3185         ) stg
3186         ON (    f.resource_id = stg.resource_id
3187             AND nvl(f.department_id, -999) = nvl(stg.department_id, -999)
3188             AND f.organization_id = stg.organization_id
3189             AND f.job_id = stg.job_id
3190             AND f.job_type = stg.job_type
3191             AND f.assembly_item_id = stg.assembly_item_id
3192             AND f.source = stg.source)
3193         WHEN MATCHED THEN UPDATE
3194         SET
3195             f.actual_qty_draft = stg.actual_qty_draft,
3196             f.actual_qty = nvl(f.actual_qty,0) - nvl(f.actual_qty_draft,0) + nvl(stg.actual_qty_draft,0) + nvl(stg.actual_qty,0),
3197 
3198             f.actual_qty_g_draft = stg.actual_qty_g_draft,
3199             f.actual_qty_g = nvl(f.actual_qty_g,0) - nvl(f.actual_qty_g_draft,0) + nvl(stg.actual_qty_g_draft,0) + nvl(stg.actual_qty_g,0),
3200 
3201             f.actual_val_b_draft = stg.actual_val_b_draft,
3202             f.actual_val_b  = nvl(f.actual_val_b,0) - nvl(f.actual_val_b_draft,0) + nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0),
3203              f.actual_val_g  = (nvl(f.actual_val_b,0) - nvl(f.actual_val_b_draft,0) + nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0))
3204                                 * stg.conversion_rate,
3205             f.actual_val_sg  = (nvl(f.actual_val_b,0) - nvl(f.actual_val_b_draft,0) + nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0))
3206                                  * stg.sec_conversion_rate,
3207 
3208             f.last_update_date  = sysdate,
3209             f.last_updated_by   = g_user_id,
3210             f.last_update_login = g_login_id
3211         WHEN NOT MATCHED THEN
3212         INSERT (
3213             f.resource_id,
3214             f.department_id,
3215             f.organization_id,
3216             f.uom,
3217             f.actual_qty_draft,
3218             f.actual_qty,
3219             f.actual_qty_g_draft,
3220             f.actual_qty_g,
3221             f.actual_val_b_draft,
3222             f.actual_val_b,
3223             f.actual_val_g,
3224             f.actual_val_sg,
3225             f.job_id,
3226             f.job_type,
3227             f.assembly_item_id,
3228             f.source,
3229             f.creation_date,
3230             f.last_update_date,
3231             f.created_by,
3232             f.last_updated_by,
3233             f.last_update_login,
3234             f.program_id,
3235             f.program_login_id,
3236             f.program_application_id,
3237             f.request_id)
3238         VALUES (
3239             stg.resource_id,
3240             stg.department_id,
3241             stg.organization_id,
3242             stg.uom,
3243             stg.actual_qty_draft,
3244             nvl(stg.actual_qty_draft,0) + nvl(stg.actual_qty,0),
3245             stg.actual_qty_g_draft,
3246             nvl(stg.actual_qty_g_draft,0) + nvl(stg.actual_qty_g,0),
3247             stg.actual_val_b_draft,
3248             nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0),
3249             (nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0)) * stg.conversion_rate,
3250             (nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0)) * stg.sec_conversion_rate,
3251             stg.job_id,
3252             stg.job_type,
3253             stg.assembly_item_id,
3254             stg.source,
3255             sysdate,
3256             sysdate,
3257             g_user_id,
3258             g_user_id,
3259             g_login_id,
3260             g_program_id,
3261             g_program_login_id,
3262             g_program_application_id,
3263             g_request_id);
3264 
3265         l_count := sql%rowcount;
3266 
3267         bis_collection_utilities.put_line('Load resource actual into FACT ' ||
3268                 l_count || ' rows, completed at '
3269                     || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
3270     --}
3271     END IF;
3272 
3273 
3274      -- Merge Avail and Actual data in to Avail Fact
3275     IF l_error_flag <> TRUE THEN
3276     --{
3277         bis_collection_utilities.put_line('Merge res actual and avail from staging to avail fact ...');
3278         l_stmt_num := 130;
3279 
3280         MERGE /*+ index(f, OPI_DBI_RES_AVAIL_F_N1) */
3281         INTO opi_dbi_res_avail_f f
3282         USING (
3283         SELECT
3284             res.resource_id,
3285             res.department_id,
3286             res.organization_id,
3287             res.transaction_date,
3288             res.uom,
3289             SUM (res.avail_qty)     avail_qty,
3290             SUM (avail_qty_g)       avail_qty_g,
3291             SUM (res.avail_val_b)   avail_val_b,
3292             SUM (res.avail_val_g)   avail_val_g,
3293             SUM (res.avail_val_sg)  avail_val_sg,
3294             SUM (res.actual_qty_draft)      actual_qty_draft,
3295             SUM (res.actual_qty)            actual_qty,
3296             SUM (res.actual_qty_g_draft)    actual_qty_g_draft,
3297             SUM (res.actual_qty_g)          actual_qty_g,
3298             SUM (res.actual_val_b_draft)    actual_val_b_draft,
3299             SUM (res.actual_val_b)          actual_val_b,
3300             min(res.conversion_rate)        conversion_rate,
3301             min(res.sec_conversion_rate)    sec_conversion_rate,
3302             res.source source
3303         FROM
3304             (SELECT
3305                 stg.resource_id,
3306                 stg.department_id,
3307                 stg.organization_id,
3308                 stg.transaction_date,
3309                 MAX (stg.uom)   uom,
3310                 NULL    avail_qty,
3311                 NULL    avail_qty_g,
3312                 NULL    avail_val_b,
3313                 NULL    avail_val_g,
3314                 NULL    avail_val_sg,
3315                 SUM (stg.actual_qty_draft)      actual_qty_draft,
3316                 SUM (stg.actual_qty)            actual_qty,
3317                 SUM (stg.actual_qty_g_draft)    actual_qty_g_draft,
3318                 SUM (stg.actual_qty_g)          actual_qty_g,
3319                 SUM (stg.actual_val_b_draft)    actual_val_b_draft,
3320                 SUM (stg.actual_val_b)          actual_val_b,
3321                 min(rate.conversion_rate)           conversion_rate,
3322                 min(rate.sec_conversion_rate)       sec_conversion_rate,
3323                 stg.source                      source
3324             FROM
3325                 opi_dbi_res_actual_stg stg,
3326                 opi_dbi_res_conv_rates rate
3327             WHERE
3328                 stg.organization_id = rate.organization_id
3329             AND stg.transaction_date  = rate.transaction_date
3330             GROUP BY
3331                 stg.resource_id,
3332                 stg.department_id,
3333                 stg.organization_id,
3334                 stg.transaction_date,
3335                 stg.source,
3336                 stg.uom
3337             UNION ALL   -- from avail staging
3338             SELECT
3339                 stg.resource_id,
3340                 stg.department_id,
3341                 stg.organization_id,
3342                 stg.transaction_date,
3343                 stg.uom,
3344                 stg.avail_qty,
3345                 stg.avail_qty_g,
3346                 stg.avail_val_b,
3347                 stg.avail_val_b * rate.conversion_rate avail_val_g,
3348                 stg.avail_val_b * rate.sec_conversion_rate avail_val_sg,
3349                 NULL actual_qty_draft,
3350                 NULL actual_qty,
3351                 NULL actual_qty_g_draft,
3352                 NULL actual_qty_g,
3353                 NULL actual_val_b_draft,
3354                 NULL actual_val_b,
3355                 rate.conversion_rate    conversion_rate,
3356                 rate.sec_conversion_rate sec_conversion_rate,
3357                 stg.source
3358             FROM
3359                 opi_dbi_res_avail_stg stg,
3360                 opi_dbi_res_conv_rates rate
3361             WHERE
3362                 stg.organization_id = rate.organization_id
3363             AND stg.transaction_date  = rate.transaction_date
3364             ) res
3365         GROUP BY
3366              res.resource_id,
3367             res.department_id,
3368             res.organization_id,
3369             res.transaction_date,
3370             res.source,
3371             res.uom
3372         ) stg
3373         ON (
3374             f.organization_id = stg.organization_id
3375             AND f.transaction_date = stg.transaction_date
3376             AND nvl(f.department_id, -999) = nvl(stg.department_id, -999)
3377             AND f.resource_id = stg.resource_id )
3378         WHEN matched THEN UPDATE SET
3379             f.uom           = stg.uom,
3380             f.avail_qty     = nvl(stg.avail_qty, f.avail_qty),
3381             f.avail_qty_g   = nvl(stg.avail_qty_g, f.avail_qty_g),
3382             f.avail_val_b   = nvl(stg.avail_val_b, f.avail_val_b),
3383             f.avail_val_g   = nvl(stg.avail_val_g, f.avail_val_g),
3384             f.avail_val_sg  = nvl(stg.avail_val_sg, f.avail_val_sg),
3385             f.source        = stg.source,
3386             f.actual_qty_draft   = nvl(stg.actual_qty_draft, f.actual_qty_draft),
3387             f.actual_qty         = nvl(f.actual_qty,0) - nvl(f.actual_qty_draft,0) + nvl(stg.actual_qty_draft,0) + nvl(stg.actual_qty,0),
3388             f.actual_qty_g_draft = nvl(stg.actual_qty_g_draft, f.actual_qty_g_draft),
3389             f.actual_qty_g       = nvl(f.actual_qty_g,0) - nvl(f.actual_qty_g_draft,0) + nvl(stg.actual_qty_g_draft,0) + nvl(stg.actual_qty_g,0),
3390             f.actual_val_b_draft = nvl(stg.actual_val_b_draft, f.actual_val_b_draft),
3391             f.actual_val_b       = nvl(f.actual_val_b,0) - nvl(f.actual_val_b_draft,0) + nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0),
3392             f.actual_val_g       = (nvl(f.actual_val_b,0) - nvl(f.actual_val_b_draft,0) + nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0))
3393                                     * stg.conversion_rate,
3394             f.actual_val_sg      = (nvl(f.actual_val_b,0) - nvl(f.actual_val_b_draft,0) + nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0))
3395                                    * stg.sec_conversion_rate,
3396             f.last_update_date   = sysdate,
3397             f.last_updated_by    = g_user_id,
3398             f.last_update_login  = g_login_id
3399         WHEN NOT matched THEN
3400         INSERT (
3401             f.resource_id,
3402             f.department_id,
3403             f.organization_id,
3404             f.transaction_date,
3405             f.uom,
3406             f.avail_qty,
3407             f.avail_qty_g,
3408             f.avail_val_b,
3409             f.avail_val_g,
3410             f.avail_val_sg,
3411             f.actual_qty_draft,
3412             f.actual_qty,
3413             f.actual_qty_g_draft,
3414             f.actual_qty_g,
3415             f.actual_val_b_draft,
3416             f.actual_val_b,
3417             f.actual_val_g,
3418             f.actual_val_sg,
3419             f.source,
3420             f.creation_date,
3421             f.last_update_date,
3422             f.created_by,
3423             f.last_updated_by,
3424             f.last_update_login,
3425             f.program_id,
3426             f.program_login_id,
3427             f.program_application_id,
3428             f.request_id)
3429         VALUES (
3430             stg.resource_id,
3431             stg.department_id,
3432             stg.organization_id,
3433             stg.transaction_date,
3434             stg.uom,
3435             stg.avail_qty,
3436             stg.avail_qty_g,
3437             stg.avail_val_b,
3438             stg.avail_val_g,
3439             stg.avail_val_sg,
3440             stg.actual_qty_draft,
3441             nvl(stg.actual_qty_draft,0) + nvl(stg.actual_qty,0),
3442             stg.actual_qty_g_draft,
3443             nvl(stg.actual_qty_g_draft,0) + nvl(stg.actual_qty_g,0),
3444             stg.actual_val_b_draft,
3445             nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0),
3446             (nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0)) * stg.conversion_rate,
3447             (nvl(stg.actual_val_b_draft,0) + nvl(stg.actual_val_b,0)) * stg.sec_conversion_rate,
3448             stg.source,
3449             Sysdate,
3450             Sysdate,
3451             g_user_id,
3452             g_user_id,
3453             g_login_id,
3454             g_program_id,
3455             g_program_login_id,
3456             g_program_application_id,
3457             g_request_id);
3458 
3459         l_count := SQL%rowcount;
3460 
3461         bis_collection_utilities.put_line('Load resource avail into FACT ' || l_count || ' rows, completed at '
3462                              || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
3463 
3464          -- update common modules for OPI
3465         l_comm_opi_avail_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => RESOURCE_VAR_ETL,
3466                                                                                 p_source => 1);
3467         l_comm_opm_avail_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => RESOURCE_VAR_ETL,
3468                                                                                 p_source => 2);
3469 
3470         l_comm_opi_actual_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => ACTUAL_RES_ETL,
3471                                                                                  p_source => 1);
3472         l_comm_opm_actual_flag := opi_dbi_common_mod_incr_pkg.etl_report_success(p_etl_id => ACTUAL_RES_ETL,
3473                                                                                  p_source => 2);
3474 
3475         IF l_comm_opi_avail_flag AND l_comm_opm_avail_flag
3476             AND l_comm_opi_actual_flag AND l_comm_opm_actual_flag THEN
3477         --{
3478             COMMIT;
3479 
3480             -- common clean up
3481 
3482             execute immediate 'truncate table ' || l_opi_schema
3483                     || '.opi_dbi_res_conv_rates ';
3484 
3485             execute immediate 'truncate table ' || l_opi_schema
3486                     || '.opi_dbi_res_avail_stg ';
3487 
3488             execute immediate 'truncate table ' || l_opi_schema
3489                     || '.opi_dbi_res_actual_stg ';
3490 
3491 
3492             bis_collection_utilities.WRAPUP( p_status => TRUE,
3493                     p_count => l_row_count,
3494                     p_message => 'successful in incremental_load_res_utl.'
3495                     );
3496         --}
3497         ELSE
3498         --{
3499             rollback;
3500             retcode := g_error ;
3501             errbuf  := 'Error in report to common modules. Please check log file for details.';
3502 
3503             bis_collection_utilities.put_line('Error in incremental_load_res_utl at ' || l_stmt_num);
3504             bis_collection_utilities.wrapup(p_status => FALSE,
3505                    p_count => 0,
3506                    p_message => 'failed in incremental_load_res_utl.'
3507                    );
3508         --}
3509         END IF;
3510     --}
3511     ELSE
3512     --{
3513         rollback;
3514         retcode := g_error;
3515         errbuf  := 'Please check log file for details.';
3516 
3517         bis_collection_utilities.put_line('Error in incremental_load_res_utl at ' || l_stmt_num);
3518         bis_collection_utilities.wrapup(p_status => FALSE,
3519                    p_count => 0,
3520                    p_message => 'failed in incremental_load_res_utl.'
3521                    );
3522     --}
3523     END IF;
3524 
3525     bis_collection_utilities.put_line('Exit incremental_load_res_utl() ' ||
3526                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
3527 
3528 EXCEPTION
3529 --{
3530     WHEN SCHEMA_INFO_NOT_FOUND THEN
3531     --{
3532         bis_collection_utilities.put_line('Schema Information was not found.');
3533         errbuf := Sqlerrm;
3534         Retcode := g_ERROR;
3535     --}
3536     WHEN OTHERS THEN
3537     --{
3538     Errbuf:= Sqlerrm;
3539     Retcode:= SQLCODE;
3540 
3541     ROLLBACK;
3542 
3543     bis_collection_utilities.put_line('Error in incremental_load_res_utl at ' || l_stmt_num);
3544     bis_collection_utilities.wrapup(p_status => FALSE,
3545                    p_count => 0,
3546                    p_message => 'failed in incremental_load_res_utl.'
3547                    );
3548 
3549     RAISE_APPLICATION_ERROR(-20000,errbuf);
3550     --}
3551 --}
3552 END incremental_load_res_utl;
3553 
3554 
3555 /*======================================================================
3556     This procedure extracts Resource Standard Usage for initial loads.
3557 
3558     Parameters:
3559     - errbuf: error buffer
3560     - retcode: return code
3561     - p_degree: degree
3562 =======================================================================*/
3563 
3564 PROCEDURE initial_load_res_std (errbuf  IN OUT NOCOPY VARCHAR2,
3565                                 retcode IN OUT NOCOPY VARCHAR2,
3566                                 p_degree    IN    NUMBER    ) IS
3567     l_stmt_num NUMBER;
3568     l_row_count NUMBER;
3569     l_err_num NUMBER;
3570     l_err_msg VARCHAR2(255);
3571     l_error_flag  BOOLEAN;
3572 
3573     l_opi_schema      VARCHAR2(30);
3574     l_status          VARCHAR2(30);
3575     l_industry        VARCHAR2(30);
3576 
3577     SCHEMA_INFO_NOT_FOUND   exception;
3578 
3579 BEGIN
3580 
3581     bis_collection_utilities.put_line('Enter initial_load_res_std() ' ||
3582                                       To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
3583 
3584     -- initialization block
3585     l_error_flag := FALSE;
3586 
3587     IF bis_collection_utilities.setup( 'OPI_DBI_RES_STD_F' ) = false THEN
3588     --{
3589         RAISE_APPLICATION_ERROR(-20000, errbuf);
3590     --}
3591     END IF;
3592 
3593     -- Performance tuning change
3594     execute immediate 'alter session set hash_area_size=100000000 ';
3595     execute immediate 'alter session set sort_area_size=100000000 ';
3596 
3597 
3598     -- setup globals
3599     l_stmt_num := 10;
3600     bis_collection_utilities.put_line('Setup global parameters ...');
3601 
3602     check_setup_globals(errbuf => errbuf, retcode => retcode);
3603 
3604     IF retcode <> 0 THEN
3605     --{
3606         RETURN ;
3607     --}
3608     END IF;
3609 
3610 
3611     -- common clean up
3612     l_stmt_num := 20;
3613     IF fnd_installation.get_app_info( 'OPI', l_status, l_industry, l_opi_schema) THEN
3614     --{
3615         execute immediate 'truncate table ' || l_opi_schema
3616         || '.opi_dbi_res_std_f PURGE MATERIALIZED VIEW LOG';
3617     --}
3618     ELSE
3619     --{
3620         RAISE SCHEMA_INFO_NOT_FOUND;
3621     --}
3622     END IF;
3623 
3624     -- If no errors, load discrete data to fact table
3625     IF l_error_flag = FALSE THEN
3626     --{
3627         bis_collection_utilities.put_line('Load discrete res std into staging ...');
3628 
3629         INSERT /*+ append parallel(opi_dbi_res_std_f) */
3630         INTO opi_dbi_res_std_f (
3631             resource_id,
3632             department_id,
3633             organization_id,
3634             transaction_date,
3635             uom,
3636             std_usage_qty,
3637             std_usage_qty_g,
3638             std_usage_val_b,
3639             std_usage_val_g,
3640             std_usage_val_sg,
3641             job_id,
3642             job_type,
3643             assembly_item_id,
3644             source,
3645             creation_date,
3646             last_update_date,
3647             created_by,
3648             last_updated_by,
3649             last_update_login,
3650             program_id,
3651             program_login_id,
3652             program_application_id,
3653             request_id )
3654         SELECT  /*+ use_hash(wor) use_hash(wo) use_hash(job)
3655                     use_hash(br) use_hash(mp)
3656                     use_hash(m) use_hash(m2) use_hash(crc) use_hash(bdr)
3657                     parallel(wor) parallel(wo) parallel(job) parallel(br)
3658                     parallel(mp) parallel(m) parallel(m2) parallel(crc)
3659                     parallel(bdr) */
3660             wor.resource_id,
3661             nvl (bdr.share_from_dept_id, wo.department_id),
3662             job.organization_id,
3663             Trunc (job.completion_date) transaction_date,
3664             br.unit_of_measure uom,
3665             SUM (Decode (basis_type,
3666                          1, wor.usage_rate_or_amount *
3667                             job.actual_qty_completed,
3668                           2, wor.usage_rate_or_amount ) )  std_usage_qty,
3669             SUM (Decode (basis_type,
3670                          1, wor.usage_rate_or_amount *
3671                             job.actual_qty_completed,
3672                          2, wor.usage_rate_or_amount )/
3673                 m.conversion_rate * m2.conversion_rate) std_usage_qty_g,
3674             SUM (Decode (basis_type,
3675                          1, wor.usage_rate_or_amount *
3676                             job.actual_qty_completed,
3677                          2, wor.usage_rate_or_amount ) * crc.resource_rate)
3678                 std_usage_val_b,
3679             SUM (Decode (basis_type,
3680                          1, wor.usage_rate_or_amount *
3681                             job.actual_qty_completed,
3682                          2, wor.usage_rate_or_amount ) * crc.resource_rate *
3683                 job.conversion_rate )  std_usage_val_g,
3684             SUM (Decode (basis_type,
3685                          1, wor.usage_rate_or_amount *
3686                             job.actual_qty_completed,
3687                          2, wor.usage_rate_or_amount ) * crc.resource_rate *
3688                 job.sec_conversion_rate )  std_usage_val_sg,
3689             job.job_id,
3690             job.job_type,
3691             job.assembly_item_id,
3692             OPI_SOURCE source,
3693             sysdate,
3694             sysdate,
3695             g_user_id,
3696             g_user_id,
3697             g_login_id,
3698             g_program_id,
3699             g_program_login_id,
3700             g_program_application_id,
3701             g_request_id
3702           FROM  wip_operation_resources     wor,
3703                 wip_operations                   wo,
3704                 opi_dbi_jobs_f               job,
3705                 bom_resources              br,
3706                 mtl_parameters                  mp,
3707                 mtl_uom_conversions             m,
3708                 mtl_uom_conversions             m2,
3709                 cst_resource_costs              crc,
3710                 bom_department_resources        bdr
3711           WHERE job.job_type IN (1,2,5) -- Discrete and Repetitive also OSFM
3712             AND job.std_res_flag = 1
3713             AND wor.organization_id = job.organization_id
3714             AND job.job_id = Nvl(wor.repetitive_schedule_id, wor.wip_entity_id)
3715             AND br.resource_id      = wor.resource_id
3716             AND wo.organization_id   = wor.organization_id
3717             AND wo.wip_entity_id     = wor.wip_entity_id
3718             AND wo.operation_seq_num = wor.operation_seq_num
3719             AND nvl(wo.repetitive_schedule_id, -999) =
3720                     nvl(wor.repetitive_schedule_id, -999)
3721              AND m.inventory_item_id  = 0
3722             AND m.uom_code           = g_hr_uom
3723             AND m2.uom_code          = br.unit_of_measure
3724             AND m2.uom_class         = m.uom_class
3725             AND m2.inventory_item_id  = 0
3726             AND mp.organization_id   = wor.organization_id
3727             AND crc.resource_id      = br.resource_id
3728             AND crc.organization_id  = mp.organization_id
3729             AND bdr.resource_id      = wor.resource_id
3730             AND bdr.department_id    = wo.department_id
3731             AND (   (mp.primary_cost_method = 1 AND crc.cost_type_id = 1)
3732                  OR (mp.primary_cost_method in (2,5,6) AND
3733                      crc.cost_type_id = mp.AVG_RATES_COST_TYPE_ID ) )
3734           GROUP BY
3735                 job.organization_id,
3736                 nvl(bdr.share_from_dept_id,wo.department_id),
3737                 job.job_id,
3738                 job.job_type,
3739                 job.assembly_item_id,
3740                 br.unit_of_measure,
3741                 wor.resource_id,
3742                 trunc(job.completion_date);
3743 
3744         l_row_count := SQL%rowcount;
3745 
3746         COMMIT;
3747 
3748         bis_collection_utilities.put_line('Load OPI resource standard into FACT ' ||
3749                 l_row_count || ' rows, completed at '
3750                 || To_char(Sysdate, 'hh24:mi:ss dd-mon-yyyy'));
3751 
3752 
3753         -- load opm res std table
3754         bis_collection_utilities.put_line('Load process res std into staging ...');
3755 
3756         initial_opm_res_std (errbuf => errbuf,
3757                              retcode => retcode,
3758                              p_degree => p_degree);
3759 
3760          -- Update std_res_flag in Job Master to 0 where std_res_flag = 1
3761         UPDATE  opi_dbi_jobs_f
3762         SET     std_res_flag = 0,
3763                 last_update_date = sysdate,
3764                 last_updated_by = g_user_id,
3765                 last_update_login = g_login_id
3766         WHERE   std_res_flag = 1;
3767 
3768         COMMIT;
3769     --}
3770     END IF ;
3771 
3772     bis_collection_utilities.WRAPUP( p_status => TRUE,
3773                                       p_count => l_row_count,
3774                                      p_message => 'successful in initial_load_res_std.');
3775 
3776 
3777 EXCEPTION
3778 --{
3779     WHEN SCHEMA_INFO_NOT_FOUND THEN
3780     --{
3781         bis_collection_utilities.put_line('Schema information was not found.');
3782     --}
3783     WHEN OTHERS THEN
3784     --{
3785     Errbuf:= Sqlerrm;
3786     Retcode:= SQLCODE;
3787 
3788     ROLLBACK;
3789     bis_collection_utilities.put_line('Error in initial_load_res_std at ' || l_stmt_num);
3790     bis_collection_utilities.wrapup(p_status => FALSE,
3791                    p_count => 0,
3792                    p_message => 'failed in initial_load_res_std'
3793                    );
3794 
3795     RAISE_APPLICATION_ERROR(-20000,errbuf);
3796     --}
3797 --}
3798 END initial_load_res_std;
3799 
3800 END opi_dbi_res_pkg;