DBA Data[Home] [Help]

PACKAGE BODY: APPS.OPI_DBI_INV_VALUE_UTL_PKG

Source


1 PACKAGE BODY OPI_DBI_INV_VALUE_UTL_PKG as
2 /* $Header: OPIDIVUB.pls 120.2 2005/08/22 23:57:01 achandak noship $ */
3 
4 g_sysdate DATE;
5 g_created_by NUMBER;
6 g_last_update_login NUMBER;
7 g_last_updated_by NUMBER;
8 
9 /*  Marker for secondary conv. rate if the primary and secondary curr codes
10     and rate types are identical. Can't be -1, -2, -3 since the FII APIs
11     return those values. */
12 C_PRI_SEC_CURR_SAME_MARKER CONSTANT NUMBER := -9999;
13 
14 -- Euro rates came into effect from 1999
15 C_EURO_START_DATE CONSTANT DATE := to_date ('01/01/1999', 'DD/MM/YYYY');
16 
17 -- GL API returns -3 if EURO rate missing on 01-JAN-1999
18 C_EURO_MISSING_AT_START CONSTANT NUMBER := -3;
19 
20 -- Conversion rate related variables: global currency code and rate type
21 s_global_curr_code  VARCHAR2(10);
22 s_global_rate_type  VARCHAR2(15);
23 
24 -- secondary global currency
25 s_secondary_curr_code  VARCHAR2(10);
26 s_secondary_rate_type  VARCHAR2(15);
27 
28 
29 
30 FUNCTION Get_Conversion_Rate (errbuf  IN OUT NOCOPY VARCHAR2,
31                               retcode IN OUT NOCOPY VARCHAR2)
32     RETURN NUMBER
33 IS
34 
35     -- for cleaning out the conversion rates table, since we insert/append
36     -- now
37     l_opi_schema VARCHAR2(30);
38     l_status VARCHAR2(30);
39     l_industry VARCHAR2(30);
40 
41     l_proc_name CONSTANT VARCHAR2(40) := 'get_conversion_name';
42     l_stmt_id NUMBER;
43 
44     -- Cursor to see if any rates are missing. See below for details
45     CURSOR invalid_rates_exist_csr IS
46         SELECT 1
47           FROM opi_dbi_conversion_rates
48           WHERE (   nvl (conversion_rate, -999) < 0
49                  OR nvl (sec_conversion_rate, 999) < 0)
50             AND rownum < 2;
51 
52     invalid_rates_exist_rec invalid_rates_exist_csr%ROWTYPE;
53 
54     -- Set up a cursor to get all the invalid rates.
55     -- By the logic of the fii_currency.get_global_rate_primary
56     -- and fii_currency.get_global_rate_secondary APIs, the returned value
57     -- is -ve if no rate exists:
58     -- -1 for dates with no rate.
59     -- -2 for unrecognized conversion rates.
60     -- -3 for missing EUR to USD rates on 01-JAN-1999 when the
61     --    transaction_date is prior to 01-JAN-1999 (when the EUR
62     --    officially went into circulation).
63     --
64     -- However, with the secondary currency, the null rate means it
65     -- has not been setup and should therefore not be reported as an
66     -- error.
67     --
68     -- Also, cross check with the org-date pairs in the staging table,
69     -- in case some orgs never had a functional currency code defined.
70     CURSOR invalid_rates_csr (p_pri_sec_curr_same NUMBER) IS
71         SELECT DISTINCT
72             report_order,
73             curr_code,
74             rate_type,
75             transaction_date,
76             f_currency_code
77           FROM (
78             SELECT DISTINCT
79                     s_global_curr_code curr_code,
80                     s_global_rate_type rate_type,
81                     1 report_order, -- ordering global currency first
82                     mp.organization_code,
83                     decode (conv.conversion_rate,
84                             C_EURO_MISSING_AT_START, C_EURO_START_DATE,
85                             conv.transaction_date) transaction_date,
86                     conv.f_currency_code
87               FROM opi_dbi_conversion_rates conv,
88                    mtl_parameters mp,
89                   (SELECT /*+ parallel (opi_dbi_onhand_stg) */
90                    DISTINCT organization_id, transaction_date
91                      FROM opi_dbi_onhand_stg
92                    UNION
93                    SELECT /*+ parallel (opi_dbi_intransit_stg) */
94                    DISTINCT organization_id, transaction_date
95                      FROM opi_dbi_intransit_stg
96                    UNION
97                    SELECT /*+ parallel (opi_dbi_wip_stg) */
98                    DISTINCT organization_id, transaction_date
99                    FROM opi_dbi_wip_stg
100                    UNION
101                    SELECT /*+ parallel (opi_dbi_inv_beg_stg) */
102                    DISTINCT organization_id, transaction_date
103                    FROM opi_dbi_inv_beg_stg
104                    UNION
105                    SELECT /*+ parallel (opi_dbi_onh_qty_stg) */
106                    DISTINCT organization_id, transaction_date
107                    FROM opi_dbi_onh_qty_stg
108                    WHERE transaction_source ='MMT'
109                    UNION
110                    SELECT /*+ parallel (opi_dbi_opm_inv_stg) */
111                    DISTINCT organization_id, transaction_date
112                      FROM opi_dbi_opm_inv_stg) to_conv -- Only change
113               WHERE nvl (conv.conversion_rate, -999) < 0 -- null is not fine
114                 AND mp.organization_id = to_conv.organization_id
115                 AND conv.transaction_date (+) = to_conv.transaction_date
116                 AND conv.organization_id (+) = to_conv.organization_id
117             UNION ALL
118             SELECT DISTINCT
119                     s_secondary_curr_code curr_code,
120                     s_secondary_rate_type rate_type,
121                     decode (p_pri_sec_curr_same,
122                             1, 1,
123                             2) report_order, --ordering secondary currency next
124                     mp.organization_code,
125                     decode (conv.sec_conversion_rate,
126                             C_EURO_MISSING_AT_START, C_EURO_START_DATE,
127                             conv.transaction_date) transaction_date,
128                     conv.f_currency_code
129               FROM opi_dbi_conversion_rates conv,
130                    mtl_parameters mp,
131                   (SELECT /*+ parallel (opi_dbi_onhand_stg) */
132                    DISTINCT organization_id, transaction_date
133                      FROM opi_dbi_onhand_stg
134                    UNION
135                    SELECT /*+ parallel (opi_dbi_intransit_stg) */
136                    DISTINCT organization_id, transaction_date
137                      FROM opi_dbi_intransit_stg
138                    UNION
139                    SELECT /*+ parallel (opi_dbi_wip_stg) */
140                    DISTINCT organization_id, transaction_date
141                      FROM opi_dbi_wip_stg
142                    UNION
143                    SELECT /*+ parallel (opi_dbi_inv_beg_stg) */
144                    DISTINCT organization_id, transaction_date
145                    FROM opi_dbi_inv_beg_stg
146                    UNION
147                    SELECT /*+ parallel (opi_dbi_onh_qty_stg) */
148                    DISTINCT organization_id, transaction_date
149                    FROM opi_dbi_onh_qty_stg
150                    WHERE transaction_source ='MMT'
151                    UNION
152                    SELECT /*+ parallel (opi_dbi_opm_inv_stg) */
153                    DISTINCT organization_id, transaction_date
154                      FROM opi_dbi_opm_inv_stg) to_conv
155               WHERE nvl (conv.sec_conversion_rate, 999) < 0 -- null is fine
156                 AND mp.organization_id = to_conv.organization_id
157                 AND conv.transaction_date (+) = to_conv.transaction_date
158                 AND conv.organization_id (+) = to_conv.organization_id)
159           ORDER BY
160                 report_order ASC,
161                 transaction_date,
162                 f_currency_code;
163 
164 
165     -- Flag to ensure all rates have been found.
166     l_all_rates_found BOOLEAN;
167 
168     -- Boolean to check if the primary and secondary currencies are the
169     -- same
170     l_pri_sec_curr_same NUMBER;
171 
172     -- for exception reporting
173     i_err_num NUMBER;
174     i_err_msg VARCHAR2(255);
175 
176 BEGIN
177 
178     BIS_COLLECTION_UTILITIES.PUT_LINE ('Get_conversion_rates: #0: Computing conversion rates for the inventory data extraction.');
179 
180     -- initialization block
181     l_stmt_id := 0;
182     l_all_rates_found := true;
183     l_pri_sec_curr_same := 0;
184     g_sysdate := sysdate;
185     g_created_by := fnd_global.user_id;
186     g_last_update_login := fnd_global.login_id;
187     g_last_updated_by := fnd_global.user_id;
188 
189     IF (NOT (fnd_installation.get_app_info
190                 ('OPI', l_status, l_industry, l_opi_schema)) ) THEN
191         return -1;
192     END IF;
193     EXECUTE IMMEDIATE   'truncate table ' || l_opi_schema ||
194                         '.OPI_DBI_CONVERSION_RATES';
195     BIS_COLLECTION_UTILITIES.put_line (
196         'OPI_DBI_CONVERSION_RATES table truncated.');
197 
198 
199     l_stmt_id := 10;
200     -- get the global currency code/rate types
201     s_global_curr_code := bis_common_parameters.get_currency_code;
202     s_secondary_curr_code := bis_common_parameters.get_secondary_currency_code;
203     s_global_rate_type := bis_common_parameters.get_rate_type;
204     s_secondary_rate_type := bis_common_parameters.get_secondary_rate_type;
205 
206     l_stmt_id := 20;
207     -- global currency and rate type must be set up
208     IF (s_global_curr_code IS NULL OR s_global_rate_type IS NULL) THEN
209         BIS_COLLECTION_UTILITIES.PUT_LINE (
210             l_proc_name || ':# ' || l_stmt_id || ': ' ||
211             'Please set up the global currency and global rate type before running any DBI collection.');
212         return -1;
213     END IF;
214 
215     l_stmt_id := 30;
216     -- Cannot of just one of secondary currency and secondary rate type
217     -- as null.
218     IF (    (s_secondary_curr_code IS NULL AND
219              s_secondary_rate_type IS NOT NULL)
220          OR (s_secondary_curr_code IS NOT NULL AND
221              s_secondary_rate_type IS NULL) ) THEN
222         BIS_COLLECTION_UTILITIES.PUT_LINE (
223             l_proc_name || ':# ' || l_stmt_id || ': ' ||
224             'Please make sure that both the secondary currency and rate type are defined, or that neither is defined.');
225         return -1;
226     END IF;
227 
228     l_stmt_id := 40;
229     -- check if the primary and secondary currencies and rate types are
230     -- identical.
231     IF (s_global_curr_code = nvl (s_secondary_curr_code, '---') AND
232         s_global_rate_type = nvl (s_secondary_rate_type, '---') ) THEN
233         l_pri_sec_curr_same := 1;
234     END IF;
235 
236 
237     l_stmt_id := 50;
238     -- compute the conversion rates
239     -- Get all the distinct organization and date pairs and the
240     -- base currency codes for the orgs into the conversion rates
241     -- work table.
242 
243     -- Use the fii_currency.get_global_rate_primary function to get the
244     -- conversion rate given a currency code and a date.
245     -- The function returns:
246     -- 1 for currency code of 'USD' which is the global currency
247     -- -1 for dates for which there is no currency conversion rate
248     -- -2 for unrecognized currency conversion rates
249     -- -3 for missing EUR to USD rates on 01-JAN-1999 when the
250     --    transaction_date is prior to 01-JAN-1999 (when the EUR
251     --    officially went into circulation).
252 
253     -- Use the fii_currency.get_global_rate_secondary to get the secondary
254     -- global rate. If the secondary currency has not been set up,
255     -- make the rate null. If the secondary currency/rate types are the
256     -- same as the primary, don't call the API but rather use an update
257     -- statement followed by the insert.
258 
259     -- By selecting distinct org and currency code from the gl_set_of_books
260     -- and hr_organization_information, take care of duplicate codes.
261     --
262     -- Since OPM uses it's own currency conversion rate logic,
263     -- just filter out rows with source = 2.
264     INSERT /*+ append parallel (opi_dbi_conversion_rates) */
265     INTO opi_dbi_conversion_rates (
266         organization_id,
267         f_currency_code,
268         transaction_date,
269         conversion_rate,
270         sec_conversion_rate,
271         creation_date,
272         last_update_date,
273         created_by,
274         last_updated_by,
275         last_update_login)
276     SELECT /*+ parallel (to_conv) parallel (curr_codes) */
277         to_conv.organization_id,
278         curr_codes.currency_code f_currency_code,
279         to_conv.transaction_date,
280         decode (curr_codes.currency_code,
281                 s_global_curr_code, 1,
282                 fii_currency.get_global_rate_primary (
283                                     curr_codes.currency_code,
284                                     to_conv.transaction_date) )
285             conversion_rate,
286         decode (s_secondary_curr_code,
287                 NULL, NULL,
288                 curr_codes.currency_code, 1,
289                 decode (l_pri_sec_curr_same,
290                         1, C_PRI_SEC_CURR_SAME_MARKER,
291                         fii_currency.get_global_rate_secondary (
292                             curr_codes.currency_code,
293                             to_conv.transaction_date)))
294             sec_conversion_rate,
295         sysdate,
296         sysdate,
297         g_created_by,
298         g_last_updated_by,
299         g_last_update_login
300       FROM
301         (SELECT /*+ parallel (opi_dbi_onhand_stg) */
302          DISTINCT organization_id, transaction_date
303            FROM opi_dbi_onhand_stg
304          UNION
305          SELECT /*+ parallel (opi_dbi_intransit_stg) */
306          DISTINCT organization_id, transaction_date
307            FROM opi_dbi_intransit_stg
308          UNION
309          SELECT /*+ parallel (opi_dbi_wip_stg) */
310          DISTINCT organization_id, transaction_date
311            FROM opi_dbi_wip_stg
312         UNION
313         SELECT /*+ parallel (opi_dbi_inv_beg_stg) */
314          DISTINCT organization_id, transaction_date
315          FROM opi_dbi_inv_beg_stg
316         UNION
317         SELECT /*+ parallel (opi_dbi_onh_qty_stg) */
318          DISTINCT organization_id, transaction_date
319          FROM opi_dbi_onh_qty_stg
320          WHERE transaction_source ='MMT'
321         UNION
322         SELECT /*+ parallel (opi_dbi_opm_inv_stg) */
323         DISTINCT organization_id, transaction_date
324           FROM opi_dbi_opm_inv_stg
325         ) to_conv,
326         (SELECT /*+ leading (hoi) full (hoi) use_hash (gsob)
327                     parallel (hoi) parallel (gsob)*/
328          DISTINCT hoi.organization_id, gsob.currency_code
329            FROM hr_organization_information hoi,
330                 gl_sets_of_books gsob
331            WHERE hoi.org_information_context  = 'Accounting Information'
332              AND hoi.org_information1  = to_char(gsob.set_of_books_id))
333         curr_codes
334       WHERE curr_codes.organization_id  = to_conv.organization_id;
335 
336 
337 
338     l_stmt_id := 55;
339     commit;   -- due to insert+append
340 
341     l_stmt_id := 60;
342     -- if the primary and secondary currency codes are the same, then
343     -- update the secondary with the primary
344     IF (l_pri_sec_curr_same = 1) THEN
345 
346         l_stmt_id := 70;
347         UPDATE /*+ parallel (opi_dbi_conversion_rates) */
348         opi_dbi_conversion_rates
349         SET sec_conversion_rate = conversion_rate;
350 
351         -- safe to commit, as before
352         l_stmt_id := 80;
353         commit;
354 
355     END IF;
356 
357     -- Check that all rates have been found and are non-negative.
358     -- If there is a problem, notify user.
359     l_stmt_id := 50;
360     OPEN invalid_rates_exist_csr;
361     FETCH invalid_rates_exist_csr INTO invalid_rates_exist_rec;
362     IF (invalid_rates_exist_csr%FOUND) THEN
363 
364         -- print the header out
365         BIS_COLLECTION_UTILITIES.writeMissingRateHeader;
366 
367         -- all rates not found
368         l_all_rates_found := false;
369 
370         FOR invalid_rate_rec IN invalid_rates_csr (l_pri_sec_curr_same)
371         LOOP
372 
373             BIS_COLLECTION_UTILITIES.writeMissingRate(
374                invalid_rate_rec.rate_type,
375                invalid_rate_rec.f_currency_code,
376                invalid_rate_rec.curr_code,
377                invalid_rate_rec.transaction_date);
378 
379         END LOOP;
380     END IF;
381 
382     l_stmt_id := 55;
383     CLOSE invalid_rates_exist_csr;
384 
385     -- If all rates not found raise an exception
386     l_stmt_id := 60;
387     IF (l_all_rates_found = FALSE) THEN
388         RETURN -1;
389     END IF;
390 
391     RETURN 0;
392 
393 EXCEPTION
394     WHEN OTHERS THEN
395         rollback;
396         i_err_num := SQLCODE;
397         i_err_msg := 'OPI_DBI_INV_VALUE_UTL_PKG.GET_CONVERSION_RATE ('
398                     || to_char(l_stmt_id)
399                     || '): '
400                     || substr(SQLERRM, 1,200);
401 
402         BIS_COLLECTION_UTILITIES.put_line('OPI_DBI_INV_VALUE_UTL_PKG.GET_CONVERSION_RATE - Error at statement ('
403                     || to_char(l_stmt_id)
404                     || ')');
405 
406         BIS_COLLECTION_UTILITIES.put_line('Error Number: ' ||  to_char(i_err_num));
407         BIS_COLLECTION_UTILITIES.put_line('Error Message: ' || i_err_msg);
408 
409         RETURN -1;
410 
411 END Get_Conversion_Rate;
412 
413 
414 -- This procedure is no more used in R12
415 FUNCTION  Check_Intransit_Availability (
416   p_org_id IN NUMBER)
417   return NUMBER
418 IS
419   /* return 0 -> Is not an intransit inventory */
420   /* return 3 -> Is a Intransit enabled intransit inventory */
421   retcode NUMBER;
422   ret NUMBER;
423 
424  /* cursor intransit_org(x_org_id NUMBER) IS
425     select 1
426       from mtl_interorg_parameters
427      where ((TO_ORGANIZATION_ID = x_org_id)
428         or (FROM_ORGANIZATION_ID = x_org_id))
429        and NVL(FOB_POINT,-99) in (1,2)
430        and rownum = 1;*/
431 BEGIN
432   ret := 0;
433   retcode := 0;
434  /* OPEN intransit_org(p_org_id);
435   FETCH intransit_org INTO ret;
436     IF intransit_org%NOTFOUND THEN
437       retcode := 0;
438     ELSE
439       retcode := 3;
440     END IF;
441   CLOSE intransit_org;*/
442   Null;
443 
444 
445   RETURN (retcode);
446 EXCEPTION
447   WHEN NO_DATA_FOUND THEN
448     return (retcode);
449 END Check_Intransit_Availability;
450 
451 
452 End OPI_DBI_INV_VALUE_UTL_PKG;