DBA Data[Home] [Help]

PACKAGE BODY: APPS.OZF_ACCRUAL_ENGINE

Source


1 PACKAGE BODY OZF_ACCRUAL_ENGINE AS
2 /* $Header: ozfacreb.pls 120.86.12020000.10 2013/03/05 07:57:22 nepanda ship $ */
3 ----------------------------------------------------------------------------------
4 -- Package Name
5 --   ozf_accrual_engine
6 -- PROCEDURES
7 --   calculate_accrual_amount
8 --   adjust_accrual
9 --   Get_Message
10 -- Purpose
11 --   Package body for accrual_engine
12 -- History
13 --   06/19/00      pjindal        Created
14 --   06/20/00      mpande         Updated 1) created new procedure CALCULATE_ACCRUAL_AMOUNT
15 --                                to fix bug assciated to accomodate rollup to more than 2 levels campaigns
16 --                                and accomodate association of multiple budgets////
17 --                                        2) Updated Procedure Adjust_accrual to accomodate above requirements
18 --                                        3) Updated Procedure Get_message for error handling
19 --                                        4) Updated call to create_utlization
20 --   12 Sep 2000  mpande          Changed contribution amount to approved amount
21 --   02 Feb 2001  mpande          Removed Accrual Fund and Benifit Limit check.
22 --   02 Feb 2001  mpande          Introduced Currency Validation
23 --   13 JUN 2001  mpande          Updated for hornet requirement
24 --   03 Aug 2001  mpande          Changed for offer_type and passing order line instead of orders
25 --   12/03/2001   mpande          Updated for different offers, update of adjustment, line quantity
26 --   01/23/2002   yzhao           object_type: ORDER_LINE - ORDER   object_id: Line id - order id,
27 --                                product_level_type = 'PRODUCT'
28 --   02/15/2002   mpande          Updated for 1) Cancelleld Order
29 --                                            2) Negative Adjustment
30 --                                            3) Created a subroutine for utilization
31 --   6/11/2002    mpande          1) Updated for Exception Handling
32 --                                2) Accrual Offers Query
33 --   7/26/2002    mpande          Bug#2459550, Return Order Bug , Fixed
34 --   1/22/2003    feliu            1)added g_universal_currency.
35 --                                2)changed ams_actbudgets_pvt.act_util_rec_type
36 --                                  to ams_fund_utilized_pvt.utilization_rec_type
37 --                                3)added more columns for utilization_rec_type record.
38 --                                4)added create_act_budgets and create_utilized_rec.
39 --                                5)changed ams_fund_adjustment_pvt.process_act_budgets call to
40 --                                  create_act_budgets and create_utilized_rec.
41 --   03/19/2003   yzhao           post to GL when order is shipped or invoiced RETURN
42 --                                added one more parameter to reprocess failed gl postings
43 --   10/23/2003   yzhao           fix bug 3156515 - PROMOTIONAL GOODS OFFER EXCEEDS THE BUDGET AMOUNT
44 --   10/14/2003   yzhao           Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
45 --   10/15/2003   kdass           11.5.10 Accrual Engine Enhancement: Added error log messages using Oracle Logging framework
46 --   10/20/2003   yzhao           when object sources from sales accrual budget, the budget is treated as fixed budget
47 --   11/12/2003   kdass           added new procedure log_message to log messages
48 --   11/19/2003   yzhao           Fix TEVA bug 3268498 - UTILIZATION JOURNALS ARE NOT BEING POSTED FOR ALL LINE ITEMS ON AN ORDER
49 --                                bug 3156149 - RMA ORDER FAILS TO CREATE JOURNAL ENTRIES TO GENERAL LEDGER
50 --   11/26/2003   kdass           added new function event_subscription
51 --   12/02/2003   yzhao           post to GL based on profile 'OZF : Create GL Entries for Orders'
52 --   12/08/2003   yzhao           fix bug 3291322 - ERRORS IN BUDGET CHECKBOOK > WHEN ACCRUAL BUDGET USED TO FUND OFF-INVOICE OFFER
53 --   12/10/2003   yzhao           fix TEVA bug 3308544 - ACCRUAL INCORRECT FROM RMAS
54 --   02/05/2004   yzhao           11.5.10 fix bug 3405449 - post to qualified budget only
55 --   02/12/2004   yzhao           fix bug 3435420 - do not post to gl for customer accrual budget with liability off
56 --                                11.5.10 gl posting for off invoice until AutoInvoice workflow is done
57 --                                        populate cust_account_id with offer's beneficiary account
58 --                                        populate reference_type/id for special pricing
59 --   05/11/2004   kdass           fixed bug 3609771
60 --   06/10/2004   feliu             fixed bug 3667697,3684809
61 --   08/03/2004   feliu            fixed bug 3813516.
62 --   14/10/2004   Ribha           Fixed Performance Bug 3917556 for queries on ra_customer_trx_all
63 --   01/31/2005   kdass           fixed 11.5.9 bug 4067266
64 --   06/08/2005   kdass           Bug 4415878 SQL Repository Fix - added the column object_id to the cursor c_old_adjustment_amount
65 --                                in procedure adjust_changed_order. Now passed object_id to the cursor c_split_line
66 --                                and added condition - AND header_id = p_header_id
67 --    06/12/2005  Ribha          R12 Changes - populate new columns bill_to_site_use_id/ship_to_site_use_id in ozf_funds_utilized_all_b
68 --   06/26/2005   Ribha          fixed bug 4173825 - get adjusted_amount from oe_price_adjustments
69 --   06/26/2005   Ribha          fixed bug 4417084 - for partial return order
70 --   07/27/2005   Feliu          add enhancement for R12 to insert order info to ozf_sales_transaction table.
71 --   08/01/2005   Ribha          R12: populate universal currency amount in ozf_funds_utilized_all_b
72 --   08/02/2005   Ribha          R12: populate new table ozf_object_fund_summary
73 --   09/21/2005   Ribha          Bug Fix 4619156
74 --   10/28/2005   Ribha          fixed bug 4676217 (same as 3697213 in 1159)
75 --   12/23/2005   kdass          Bug 4778995 - removed columns month_id/quarter_id/year_id
76 --   03/31/2006   kdass          fixed bug 5101720
77 --   11/09/2006   kpatro         fixed bug 5523042
78 --   20/09/2006   kpatro         fixed bug 5485334
79 --   02/24/2007   kdass          fixed bug 5485334 - issue 2
80 --   03/24/2007   kdass          fixed bug 5900966
81 --   04/11/2007   kdass          fixed bug 5953774
82 --   05/11/2007   nirprasa       fixed bug 6021635
83 --   05/11/2007   nirprasa       fixed bug 6140826 - don't post to GL the utilization amount having orig_utilization_id as -1
84 --   10/01/2007   nirprasa       fixed bug 6373391
85 --   19/12/2007   psomyaju       Ship-Debit R12.1 Enhancement: Added code for custom_setup_id 10445
86 --   17/01/2008   nirprasa       Ship-Debit R12.1 Offer Enhancement:   1)Create utilization even if committed amount is zero.
87 --   17/01/2008   nirprasa       Ship-Debit R12.1 Autopay Enhancement: 2)bill_to_site_use_id was incorrect in ozf_funds_utilized_all_b
88 --                                                                       table when offer's autopay party is Customer Name/Customer Bill To
89 --   21/04/2008   psomyaju       bug 6278466 - FP:11510-R12 6051298 - FUNDS EARNED NOT RECOGNISED AS ELIGBLE FOR CLAIM AND AUTO
90 --   09/06/2008   nirprasa       bug 7157394 - put the org_id assignment done for bug 6278466 only if beneficiary is not a customer.
91 --                                             Also, remove the initialization of org_id
92 --   09/19/2008   nirprasa       bug 6998502 - VOLUME OFFERS ARE NOT APPLIED CORRECTLY ON A SALES ORDER
93 --   11/09/2008   psomyaju       bug 7431334 - GL ENTRIES ON OFF-INVOICE DISCOUNTS CREATED ON
94 --   11/24/2008   nirprasa       bug 7030415 - R12SIP WE CAN'T SETUP CURRENY CONVERSION TYPE FOR SPECIFIC OPERATING UNIT
95 --   02/18/2009   kdass          bug 8258508 - TST1211:UNABLE TO CREATE CLAIM FOR CHILD BATCHES
96 --   04/24/2009   kpatro         bug 8463331 - FP:7567852:NO EARNED/PAID AMT IF RMA ORDER IS REFERENCED TO ORIGINAL  ORDER
97 --   05/04/2009   kdass          fixed bug 8421406 - BENEFICIARY WITHIN THE MARKET OPTIONS DO NOT WORK
98 --   06/25/2009   nirprasa       bug 7654383 - FP:7491702:CREATE GL ENTRY FAILS FOR OFFERS FOR OBSOLECTED CODE IN R12
99 --   06/25/2009   nirprasa       bug 8435487 - FP:8434980:OZF-TM : F ACCRUAL ENGINE JOB RUNNING MORE THAN 20 HRS FOR
100 --   06/25/2009   nirprasa       bug 8435499 - FP:8203657:WRONG ASO EVENT GENERATED WHEN WHEN REQUEST DATE AND PRICIN
101 --   08/13/2009   kdass          bug 8253115 - FP: 11.5.10-R12 7651889 - OZF_FUND_UTILIZED_ALL_B CONTAINS MODIFIERS LINE DELET
102 --   1/11/2010    nepanda        Bug 9269593 - transfer to gl process is erroring out ec03 error : FP for bug 8994266
103 --   2/17/2010    nepanda        Bug 9131648 : multi currency changes
104 --   03/09/2010   bkunjan        Bug 9382547 - ER SLA Uptake in Channel Revenue Management.
105 --   07/05/2010   kdass          FP bug 9470625 - MULTIPLE BATCH LINES FOR THE SAME UTILIZATION ENTRY
106 --   09/22/2010   nepanda        Fixed bug 10130256 : FUNDS ACCRUAL ERRORS OUT ON RETURN ORDER FOR OFF INVOICE OFF
107 --   10/21/2010   nirprasa       ER 10216374/9447673 SSD-IDSM ER - IDSM AND ACCRUAL CHANGES
108 --   08/27/2011   kdass          Bug 12912760 - BENEFICIARY UNDER MARKET OPTIONS IS IGNORED WHEN BUDGET EARNINGS ARE CREATED
109 --   09/03/2011   kdass          Bug 12946941 - FAE IS GENERATING INCORRECT ACCRUALS FOR SSD REQUESTS DURING PARTIAL SHIPMENT
110 --   10/5/2011    nepanda        Fix for bug 12911854 : rounded the amount values in ozf_act_budgets table
111 --   15/06/2011   BKUNJAN        Fix for Bugs 11670604 and 13054280
112 --   11/08/2011   BKUNJAN        ER 13333298 - SIEBEL TPM UPGRADE ER - ACCRUAL PROCESSING
113 --   12/26/2011   kdass          Bug 13517522 - TRANSACTIONS IN XLA_EVENTS WITH STATUS NOT PROCESSED EVEN THOUGH IS 'U' STATUS
114 --   05/Jan/2011  APYADAV        Bug 13529250 - CLAIM SETTLEMENT FETCHER ERRORS, BUDGET AMOUNT MUST BE GREATER THAN 0
115 --                                      correct values of l_orig_amt and l_rollup_orig_amt for Sales Accrual Budget.
116 --   12/Jan/2012   nirprasa      Bug 13463758 MULTIPLE BATCH LINES FOR A SALES ORDER WITH MULTIPLE SALES ORDER LINES IN DIFFER
117 --   23-Jan-2012   ninarasi      Bug 13530939 Added year id changes which got missed out (Was originally added in version 120.56.12010000.22)
118 --   26/Feb/2012   nirprasa      Bug 13742169 AIT: FAE PERFORMANCE ISSUE - meeged 120.56.12010000.36 + bugfix 13742169
119 --   29/Mar/2012   nirprasa      Bug 13824967  FAILED TRANSACTIONS IN OZF_FUNDS_UTILIZED_ALL_B
120 --   31/Oct/2012   ninarasi      Bug 14750730 SUB LEDGER ACCOUNTING ERRORS DUE TO A TERMINATED OFFER
121 --   30/Nov/2012   ninarasi      Bug 15877269 OFFER IN TRADE PLANNING CREATING IMPROPER ADJUSTMENTS
122 --   01/16/2013    ninarasi      Bug 16029659 - OFFER IN TRADE PLANNING CREATING IMPROPER ADJUSTMENTS
123 --    1/29/2013    nepanda	 Bug 16235187 - ER - MULTI UOM FULFILLMENT WITH CATCH WEIGHT
124 --   3/5/2013      nepanda       Bug 16434010 - chrm - catch weight : fae failure
125 -------------------------------------------------------------------------------
126    g_pkg_name   CONSTANT VARCHAR2 (30) := 'OZF_ACCRUAL_ENGINE';
127    g_recal_flag CONSTANT VARCHAR2(1) :=  NVL(fnd_profile.value('OZF_BUDGET_ADJ_ALLOW_RECAL'),'N');
128    g_debug_flag      VARCHAR2 (1) := 'N';
129    G_DEBUG      BOOLEAN := FND_MSG_PUB.check_msg_level(FND_MSG_PUB.g_msg_lvl_debug_high);
130    g_universal_currency   CONSTANT VARCHAR2 (15) := fnd_profile.VALUE ('OZF_UNIV_CURR_CODE');
131    g_order_gl_phase   CONSTANT VARCHAR2 (15) := NVL(fnd_profile.VALUE ('OZF_ORDER_GLPOST_PHASE'), 'SHIPPED');
132    g_bulk_limit  CONSTANT NUMBER := 5000;  -- yzhao: Sep 8,2005 bulk fetch limit. It should get from profile.
133    g_message_count NUMBER := -1; --nirprasa, added for bug 8435487 to restrict thenumber of ASO messages to be processed
134     --//13333298
135    G_TPM_PROCESS_ENABLED VARCHAR2 (1) := NVL(fnd_profile.VALUE ('OZF_TPM_PROCESS_ENABLED'),'N');
136 
137 
138    TYPE utilIdTbl       IS TABLE OF ozf_funds_utilized_all_b.utilization_id%TYPE;
139    TYPE objVerTbl       IS TABLE OF ozf_funds_utilized_all_b.object_version_number%TYPE;
140    TYPE amountTbl       IS TABLE OF ozf_funds_utilized_all_b.amount%TYPE;
141    TYPE planTypeTbl     IS TABLE OF ozf_funds_utilized_all_b.plan_type%TYPE;
142    TYPE planIdTbl       IS TABLE OF ozf_funds_utilized_all_b.plan_id%TYPE;
143    TYPE planAmtTbl      IS TABLE OF ozf_funds_utilized_all_b.plan_curr_amount%TYPE;
144    TYPE utilTypeTbl     IS TABLE OF ozf_funds_utilized_all_b.utilization_type%TYPE;
145    TYPE fundIdTbl       IS TABLE OF ozf_funds_utilized_all_b.fund_id%TYPE;
146    TYPE acctAmtTbl      IS TABLE OF ozf_funds_utilized_all_b.acctd_amount%TYPE;
147    TYPE glDateTbl       IS TABLE OF ozf_funds_utilized_all_b.gl_date%TYPE;
148    TYPE orgIdTbl        IS TABLE OF ozf_funds_utilized_all_b.org_id%TYPE;
149    TYPE priceAdjTbl     IS TABLE OF ozf_funds_utilized_all_b.price_adjustment_id%TYPE         ;
150    TYPE objectIdTbl     IS TABLE OF ozf_funds_utilized_all_b.object_id%TYPE         ;
151 
152    TYPE orderLineIdTbl  IS TABLE OF ozf_funds_utilized_all_b.order_line_id%TYPE;
153 
154    --nirprasa, ER 8399134
155    TYPE excDateTbl          IS TABLE OF ozf_funds_utilized_all_b.exchange_rate_date%TYPE;
156    TYPE excTypeTbl          IS TABLE OF ozf_funds_utilized_all_b.exchange_rate_type%TYPE;
157    TYPE currCodeTbl         IS TABLE OF ozf_funds_utilized_all_b.currency_code%TYPE;
158    TYPE planCurrCodeTbl     IS TABLE OF ozf_funds_utilized_all_b.plan_currency_code%TYPE;
159    TYPE fundReqCurrCodeTbl  IS TABLE OF ozf_funds_utilized_all_b.fund_request_currency_code%TYPE;
160    TYPE planCurrAmtTbl      IS TABLE OF ozf_funds_utilized_all_b.plan_curr_amount%TYPE;
161    TYPE planCurrAmtRemTbl   IS TABLE OF ozf_funds_utilized_all_b.plan_curr_amount_remaining%TYPE;
162    TYPE univCurrAmtTbl      IS TABLE OF ozf_funds_utilized_all_b.univ_curr_amount%TYPE;
163 
164    TYPE purchase_price_cursor_type is ref cursor; --ER9447673
165 ----------------------------------------------------------------------------------
166 -- Procedure Name
167 --  calculate_accrual_amount
168 -- created by mpande 07/20/2000
169 -- 02/13/2002 updated for negative adjustment amount
170 -- Purpose
171 --   This procedure will accept p_src_id which could be a CAMP_id or a FUND_ID
172 -- and return a PL/SQL table which consists all the funds rolled up to the first level
173 -- with  its contribution amount
174 -----------------------------------------------------------------------------------
175 
176 PROCEDURE calculate_accrual_amount (
177       x_return_status   OUT NOCOPY      VARCHAR2,
178       p_src_id          IN       NUMBER,
179       p_earned_amt      IN       NUMBER,
180       p_cust_account_type IN     VARCHAR2 := NULL,
181       p_cust_account_id IN       NUMBER  := NULL,
182       p_product_item_id IN       NUMBER  := NULL,
183       x_fund_amt_tbl    OUT NOCOPY      ozf_fund_amt_tbl_type
184    ) IS
185 
186 -- rimehrot, for R12: query from the new table
187 
188      CURSOR c_budget (p_src_id IN NUMBER) IS
189         SELECT fund_id parent_source_id, committed_amt total_amount , fund_currency parent_curr
190         FROM ozf_object_fund_summary
191         WHERE object_type = 'OFFR'
192         AND object_id = p_src_id
193         --AND NVL(committed_amt, 0) <> 0
194         ORDER BY fund_id;
195 
196       --- local variables
197       l_count           NUMBER            := 0;
198       l_return_status   VARCHAR2 (30);
199       l_msg_count                  NUMBER;
200       l_msg_data                   VARCHAR2 (2000);
201       l_rate            NUMBER;
202       l_total_amount    NUMBER            := 0;
203       l_budget_offer_yn  VARCHAR2(1);
204       l_utilized_amount    NUMBER;
205       l_eligible_fund_amt_tbl        ozf_fund_amt_tbl_type;
206       l_eligible_count  NUMBER            := 0;
207       l_eligible_total_amount      NUMBER  := 0;
208       l_eligible_flag              BOOLEAN := false;
209       l_converted_amt       NUMBER;
210       l_count1 NUMBER :=0;
211       l_total_amount1 NUMBER :=0;
212 
213       TYPE parentIdType     IS TABLE OF ozf_object_fund_summary.fund_id%TYPE;
214       TYPE amountType       IS TABLE OF ozf_object_fund_summary.committed_amt%TYPE;
215       TYPE currencyType     IS TABLE OF ozf_object_fund_summary.fund_currency%TYPE;
216       TYPE fraction_tbl_type IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
217       l_parent_id_tbl       parentIdType;
218       l_total_amount_tbl    amountType;
219       l_parent_curr_tbl     currencyType;
220       l_fraction_tbl    fraction_tbl_type;
221 
222       -- cursor for accrual budget
223       CURSOR c_offer_info  IS
224          SELECT NVL(budget_offer_yn,'N')
225          FROM ozf_offers
226          WHERE qp_list_header_id = p_src_id;
227       -- cursor for accrual fund
228       CURSOR c_fund  IS
229          SELECT fund_id , currency_code_tc
230          FROM ozf_funds_all_b
231          WHERE plan_id = p_src_id;
232 
233       /* yzhao: 10/03/2003 fix bug 3156515 - PROMOTIONAL GOODS OFFER EXCEEDS THE BUDGET AMOUNT
234                    get utilized amount.
235            -- rimehrot, commented for R12: use ozf_object_fund_summary table directly.
236            CURSOR c_get_utilized_amount(p_offer_id IN NUMBER, p_fund_id IN NUMBER) IS
237            SELECT   SUM(NVL(a2.amount, 0)) amount
238            FROM   ozf_funds_utilized_all_b a2
239            WHERE  a2.plan_id = p_offer_id
240            AND  a2.plan_type = 'OFFR'
241            AND  a2.fund_id = p_fund_id
242            AND  a2.utilization_type NOT IN ('REQUEST', 'TRANSFER', 'SALES_ACCRUAL');
243         */
244           -- rimehrot, for R12: use ozf_object_fund_summary directly to get utilized amount.
245       CURSOR c_get_utilized_amount(p_offer_id IN NUMBER, p_fund_id IN NUMBER) IS
246          SELECT utilized_amt
247          FROM ozf_object_fund_summary
248          WHERE fund_id = p_fund_id
249          AND object_type = 'OFFR'
250          AND object_id = p_offer_id;
251 
252    BEGIN
253       x_return_status            := fnd_api.g_ret_sts_success;
254 
255       IF g_debug_flag = 'Y' THEN
256          ozf_utility_pvt.write_conc_log('    D: ENTER calculate_accrual_amount   offer_id=' || p_src_id || '  p_earned_amt=' || p_earned_amt);
257       END IF;
258 
259       /*  kdass 31-JAN-05 - fix 11.5.9 bug 4067266 - RETROACTIVE VOLUME BUDGETS DO NOT CALCULATE CORRECTLY WHEN THE 1ST TIER IS AT 0%
260       IF p_earned_amt = 0 THEN
261          RETURN;
262       END IF;
263       */
264       -- check if it is a accrual budget
265       OPEN c_offer_info;
266       FETCH c_offer_info INTO l_budget_offer_yn ;
267       CLOSE c_offer_info;
268       -- For positive accruals for a fully accrued budget we have only one budget for that
269       /* yzhao: 04/04/2003 for fully accrued budget, only one budget. No matter it's positive or negative(return)
270       IF p_earned_amt > 0 AND l_budget_offer_yn = 'Y' THEN
271        */
272       IF l_budget_offer_yn = 'Y' THEN
273          l_count := 1;
274          OPEN c_fund;
275          FETCH c_fund INTO      x_fund_amt_tbl (l_count).ofr_src_id,
276                                 x_fund_amt_tbl (l_count).budget_currency;
277          CLOSE c_fund;
278          x_fund_amt_tbl (l_count).earned_amount := p_earned_amt;
279          RETURN ;
280       END IF ;
281 
282       -- first get the total committed amount
283       OPEN c_budget (p_src_id);
284       LOOP
285         FETCH c_budget BULK COLLECT INTO l_parent_id_tbl, l_total_amount_tbl, l_parent_curr_tbl LIMIT g_bulk_limit;
286 
287         FOR i IN NVL(l_parent_id_tbl.FIRST, 1) .. NVL(l_parent_id_tbl.LAST, 0) LOOP
288             -- if recalculate is allowed, always calculate based on committed amount
289             -- otherwise, calculate based on available amount
290             IF g_recal_flag = 'Y' THEN
291                 l_count := l_count + 1;
292                 x_fund_amt_tbl (l_count).ofr_src_id := l_parent_id_tbl(i);
293                 x_fund_amt_tbl (l_count).earned_amount := l_total_amount_tbl(i);
294                 x_fund_amt_tbl (l_count).budget_currency:= l_parent_curr_tbl(i);
295             ELSE
296                 -- recalculate is not allowed, always calculate based on available amount
297                /* yzhao: 10/03/2003 fix bug 3156515 - PROMOTIONAL GOODS OFFER EXCEEDS THE BUDGET AMOUNT
298                            fraction calculation: this budget's committed amount for this offer / all budget's total committed amount for this offer
299                            for positive accrual posting,
300                                if recalculate committed flag is ON, posting amount = p_earned_amount * fraction
301                                else, posting amount = LEAST(p_earned_amount * fraction, this budget's committed amount - utilized amount)
302                            for negative accrual posting,
303                                posting amount = -LEAST(abs(p_earned_amount) * fraction, this budget's committed amount - utilized amount)
304                */
305                OPEN c_get_utilized_amount( p_offer_id => p_src_id
306                                          , p_fund_id => l_parent_id_tbl(i));
307                FETCH c_get_utilized_amount INTO l_utilized_amount;
308                CLOSE c_get_utilized_amount;
309 
310                IF g_debug_flag = 'Y' THEN
311                    ozf_utility_pvt.write_conc_log('l_total_amount_tbl(i) = ' || l_total_amount_tbl(i) );
312                    ozf_utility_pvt.write_conc_log('l_utilized_amount = ' || l_utilized_amount );
313                    ozf_utility_pvt.write_conc_log('p_earned_amt = ' || p_earned_amt );
314                 END IF;
315 
316                -- nepanda : fixed bug 10130256 : The below jump will only be for positive accruals. Negative accruals will be allowed even if budget is fully utilized
317                IF l_total_amount_tbl(i) <= l_utilized_amount AND NVL(p_earned_amt, 0) > 0 THEN   -- !!! think about negative utilized amount!
318                   -- no available amount. next iteration
319                   GOTO LABEL_FOR_NEXT_ITERATION;
320                END IF;
321 
322                l_count := l_count + 1;
323                x_fund_amt_tbl (l_count).ofr_src_id := l_parent_id_tbl(i);
324 
325                -- nepanda : fixed bug 10130256
326                IF(NVL(p_earned_amt, 0) < 0) AND NVL(l_total_amount_tbl(i), 0) = NVL(l_utilized_amount, 0)  THEN  -- if Return order
327                     x_fund_amt_tbl (l_count).earned_amount := NVL(p_earned_amt, 0) * -1;
328                ELSE
329                     x_fund_amt_tbl (l_count).earned_amount := l_total_amount_tbl(i) - NVL(l_utilized_amount, 0);
330                END IF;
331                x_fund_amt_tbl (l_count).budget_currency:= l_parent_curr_tbl(i);
332             END IF;  -- IF g_recal_flag = 'Y'
333 
334             IF g_debug_flag = 'Y' THEN
335                ozf_utility_pvt.write_conc_log('    D: calculate_accrual_amount: ' || l_count || ') fund_id=' || x_fund_amt_tbl (l_count).ofr_src_id
336                   || ' utilized_amount=' || l_utilized_amount || x_fund_amt_tbl (l_count).budget_currency);
337             END IF;
338             -- if the currencies of the budgets are different then convert it into the first budget currency
339             -- to get the total amount
340             IF l_count  > 1 THEN
341                IF x_fund_amt_tbl (l_count).budget_currency <>
342                                                        x_fund_amt_tbl (l_count - 1).budget_currency THEN
343                   ozf_utility_pvt.convert_currency (
344                      x_return_status=> x_return_status,
345                      p_from_currency=> x_fund_amt_tbl (l_count).budget_currency,
346                      p_to_currency=> x_fund_amt_tbl (l_count - 1).budget_currency,
347                      p_from_amount=> x_fund_amt_tbl (l_count).earned_amount,
348                      x_to_amount=> l_converted_amt,
349                      x_rate=> l_rate
350                   );
351                   x_fund_amt_tbl (l_count).earned_amount := l_converted_amt;
352 
353                END IF;
354                l_total_amount := l_total_amount + x_fund_amt_tbl (l_count).earned_amount;
355             ELSE
356                l_total_amount := x_fund_amt_tbl (l_count).earned_amount;
357             END IF;
358 
359             If l_parent_id_tbl.COUNT > 1 THEN
360                ozf_budgetapproval_pvt.check_budget_qualification(
361                   p_budget_id          => x_fund_amt_tbl (l_count).ofr_src_id
362                 , p_cust_account_id    => p_cust_account_id
363                 , p_product_item_id    => p_product_item_id
364                 , x_qualify_flag       => l_eligible_flag
365                 , x_return_status      => l_return_status
366                 , x_msg_count          => l_msg_count
367                 , x_msg_data           => l_msg_data
368                );
369 
370                IF g_debug_flag = 'Y' THEN
371                   ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): check_budget_qualification status:   ' || l_return_status);
372                END IF;
373                IF l_return_status <> fnd_api.g_ret_sts_success THEN
374                   l_eligible_flag := false;
375                END IF;
376             ELSE
377                l_eligible_flag := true;
378             END IF;
379 
380             IF l_eligible_flag THEN
381                IF g_debug_flag = 'Y' THEN
382                   ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): budget ' || x_fund_amt_tbl (l_count).ofr_src_id
383                      || ' is qualified for product:' || p_product_item_id || ' customer: ' || p_cust_account_id);
384                END IF;
385                l_eligible_count := l_eligible_count + 1;
386                l_eligible_fund_amt_tbl (l_eligible_count).ofr_src_id := x_fund_amt_tbl (l_count).ofr_src_id;
387                l_eligible_fund_amt_tbl (l_eligible_count).earned_amount := x_fund_amt_tbl (l_count).earned_amount;
388                l_eligible_fund_amt_tbl (l_eligible_count).budget_currency:= x_fund_amt_tbl (l_count).budget_currency;
389                l_eligible_total_amount := l_eligible_total_amount + l_eligible_fund_amt_tbl (l_eligible_count).earned_amount;
390             ELSE
391                IF g_debug_flag = 'Y' THEN
392                   ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): budget ' || x_fund_amt_tbl (l_count).ofr_src_id
393                      || ' is not qualified for product:' || p_product_item_id || ' customer: ' || p_cust_account_id);
394                END IF;
395             END IF;
396 
397             <<LABEL_FOR_NEXT_ITERATION>>
398             NULL;
399         END LOOP;  -- FOR i IN NVL(l_parent_id_tbl.FIRST, 1) .. NVL(l_parent_id_tbl.LAST, 0) LOOP
400         EXIT WHEN c_budget%NOTFOUND;
401       END LOOP;  -- c_budget
402       CLOSE c_budget;
403 
404       IF g_debug_flag = 'Y' THEN
405            ozf_utility_pvt.write_conc_log('After the loop l_eligible_total_amount = ' || l_eligible_total_amount );
406       END IF;
407 
408       IF l_eligible_total_amount > 0 THEN
409           x_fund_amt_tbl.DELETE;
410           x_fund_amt_tbl := l_eligible_fund_amt_tbl;
411           l_total_amount := l_eligible_total_amount;
412           l_count := l_eligible_count;
413           IF g_debug_flag = 'Y' THEN
414              ozf_utility_pvt.write_conc_log('    D: calculate_accrual_amount(): ' || l_count
415                 || ' eligible budgets found. Total amount available for posting:' || l_total_amount);
416           END IF;
417       END IF;
418 
419       -- nepanda : fixed bug 10130256 : Removed the check for p_earned_amt < 0.
420       -- It will raise an exception when total committed amount is utilized and still trying create accruals from the budget.
421       -- With the exception raised, the message will goto EXCEPTION queue
422       -- And once you add another budget to the offer and RUN FAE with Run Exception Message param as Yes, the accruals will be created for the offer/budget.
423       -- Note that the amounts are in one currency
424       IF l_total_amount = 0 THEN
425          IF g_recal_flag = 'N'  THEN --and p_earned_amt < 0 THEN    -- ??? really needed ???
426             x_return_status            := fnd_api.g_ret_sts_error;
427             RETURN;
428          END IF;
429       END IF;
430 
431       IF g_debug_flag = 'Y' THEN
432          ozf_utility_pvt.write_conc_log('    D: calculate_accrual_amount(): g_recal_flag=' || g_recal_flag || ' p_earned_amt=' || p_earned_amt
433             || ' final sourcing budget table count=' || x_fund_amt_tbl.COUNT || ' sourcing budgets total amount=' || l_total_amount);
434       END IF;
435 
436       -- calculate the fraction if recalculation flag is on, or to_post amount is less than available amount
437       -- otherwise, use whatever available amount
438       IF g_recal_flag = 'Y' OR p_earned_amt < l_total_amount THEN
439           FOR i IN NVL (x_fund_amt_tbl.FIRST, 1) .. NVL (x_fund_amt_tbl.LAST, 0)
440           LOOP
441              IF l_total_amount = 0 THEN
442                  l_fraction_tbl (x_fund_amt_tbl (i).ofr_src_id) := 1;
443              ELSE
444                  l_fraction_tbl (x_fund_amt_tbl (i).ofr_src_id) :=
445                                                       x_fund_amt_tbl (i).earned_amount / l_total_amount;
446              END IF;
447           END LOOP;
448 
449           --nirprasa, ER 8399134
450           l_total_amount1 := p_earned_amt;
451           l_count1 := x_fund_amt_tbl.COUNT;
452 
453           IF g_debug_flag = 'Y' THEN
454           ozf_utility_pvt.write_conc_log ('x_fund_amt_tbl.COUNT '||x_fund_amt_tbl.COUNT);
455           ozf_utility_pvt.write_conc_log ('l_total_amount '||l_total_amount1);
456           ozf_utility_pvt.write_conc_log ('x_fund_amt_tbl.FIRST '|| x_fund_amt_tbl.FIRST);
457           END IF;
458           FOR i IN NVL (x_fund_amt_tbl.FIRST, 1) .. NVL (x_fund_amt_tbl.LAST, 0)
459           LOOP
460               --nirprasa, ER 8399134 to prorate the last record to resolve rounding issue
461               IF i = x_fund_amt_tbl.COUNT AND i > 1 THEN
462                  x_fund_amt_tbl (i).earned_amount := l_total_amount1;
463               ELSE
464               x_fund_amt_tbl (i).earned_amount :=
465                            p_earned_amt * l_fraction_tbl (x_fund_amt_tbl (i).ofr_src_id);
466                  l_total_amount1 := l_total_amount1 - x_fund_amt_tbl (i).earned_amount;
467               END IF;
468               IF g_debug_flag = 'Y' THEN
469                  ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): --index--'  || i  || '--final posting amt--'
470                                 || x_fund_amt_tbl (i).earned_amount
471                                 || '--fund id--' || x_fund_amt_tbl (i).ofr_src_id
472                                 || '--fraction--' || l_fraction_tbl(x_fund_amt_tbl (i).ofr_src_id));
473               END IF;
474           END LOOP;
475       END IF;
476 
477    EXCEPTION
478       WHEN OTHERS THEN
479          IF c_budget%ISOPEN THEN
480             CLOSE c_budget;
481          END IF;
482          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
483             fnd_msg_pub.add_exc_msg (g_pkg_name, 'Calculate Accrual');
484          END IF;
485          x_return_status            := fnd_api.g_ret_sts_unexp_error;
486    END calculate_accrual_amount;
487 
488   /*****************************************************************************************/
489 -- Start of Comments
490 --
491 -- NAME
492 --   Create_Act_Budgets
493 --
494 -- PURPOSE
495 --   This procedure is to create a act_budget record
496 --
497 -- HISTORY
498 -- 01/22/2003  feliu  CREATED
499 
500 -- End of Comments
501 /*****************************************************************************************/
502    PROCEDURE create_actbudgets_rec (
503       x_return_status      OUT NOCOPY      VARCHAR2
504      ,x_msg_count          OUT NOCOPY      NUMBER
505      ,x_msg_data           OUT NOCOPY      VARCHAR2
506      ,x_act_budget_id      OUT NOCOPY      NUMBER
507      ,p_act_budgets_rec    IN              ozf_actbudgets_pvt.act_budgets_rec_type
508      ,p_ledger_id          IN              NUMBER
509      ,p_org_id             IN              NUMBER DEFAULT NULL -- added for bug 7030415
510     ) IS
511       l_api_name      CONSTANT VARCHAR2 (30)        := 'create_actbudgets_rec';
512       l_full_name     CONSTANT VARCHAR2 (60)        :=    g_pkg_name
513                                                        || '.'
514                                                        || l_api_name;
515       l_return_status         VARCHAR2 (1); -- Return value from procedures
516       l_act_budgets_rec       ozf_actbudgets_pvt.act_budgets_rec_type := p_act_budgets_rec;
517       l_requester_id          NUMBER;
518       l_activity_id           NUMBER;
519       l_obj_ver_num           NUMBER;
520       l_old_approved_amount   NUMBER;
521       l_set_of_book_id        NUMBER;
522       l_sob_type_code         VARCHAR2(30);
523       l_fc_code               VARCHAR2(150);
524       l_exchange_rate_type    VARCHAR2(150);
525       l_exchange_rate         NUMBER;
526       l_approved_amount_fc    NUMBER;
527       l_old_amount_fc         NUMBER;
528       l_plan_currency         VARCHAR2(150);
529       l_rate                  NUMBER;
530 
531       CURSOR c_act_budget_id IS
532          SELECT ozf_act_budgets_s.NEXTVAL
533          FROM DUAL;
534 
535       CURSOR c_act_util_rec (p_used_by_id IN NUMBER, p_used_by_type IN VARCHAR2) IS
536          SELECT activity_budget_id, object_version_number, approved_amount,approved_amount_fc
537          FROM ozf_act_budgets
538          WHERE act_budget_used_by_id = p_used_by_id
539          AND arc_act_budget_used_by = p_used_by_type
540          AND transfer_type = 'UTILIZED';
541 
542       -- added for bug 7030415
543       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
544          SELECT exchange_rate_type
545          FROM   ozf_sys_parameters_all
546          WHERE  org_id = p_org_id;
547 
548       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
549          SELECT nvl(transaction_currency_code,fund_request_curr_code) offer_currency_code
550          FROM   ozf_offers
551          WHERE  qp_list_header_id = p_offer_id;
552 
553       -- nepanda Fix for bug 12911854
554       l_fc_currency_code VARCHAR2(150);
555       CURSOR c_get_gl_info(p_ledger_id IN NUMBER) IS
556       SELECT currency_code
557       FROM   gl_ledgers_public_v
558       WHERE  ledger_id = p_ledger_id;
559 
560    BEGIN
561       IF g_debug_flag = 'Y' THEN
562          ozf_utility_pvt.write_conc_log(   l_full_name
563                                      || ': start');
564       END IF;
565       -- Standard Start of API savepoint
566       SAVEPOINT create_actbudgets_rec;
567 
568       --  Initialize API return status to success
569       x_return_status            := fnd_api.g_ret_sts_success;
570       /* Added for bug 7030415
571        This currency conversion is for approved_amount_fc column in ozf_act_budgets table.
572        Using the utilization org_id because to_currency is the functional currency of
573        order's org's ledger.*/
574 
575       OPEN c_get_conversion_type(p_org_id);
576       FETCH c_get_conversion_type INTO l_exchange_rate_type;
577       CLOSE c_get_conversion_type;
578 
579         IF g_debug_flag = 'Y' THEN
580           ozf_utility_pvt.write_conc_log('**************************START****************************');
581           ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_act_budgets_rec.request_amount );
582           ozf_utility_pvt.write_conc_log(l_api_name||' From Curr: '||l_act_budgets_rec.request_currency );
583           ozf_utility_pvt.write_conc_log(l_api_name||' p_ledger_id: '||p_ledger_id);
584           ozf_utility_pvt.write_conc_log(l_api_name||' l_exchange_rate_type: '|| l_exchange_rate_type);
585           ozf_utility_pvt.write_conc_log('Request amount is converted from request curr to functional curr');
586         END IF;
587 
588       IF l_act_budgets_rec.request_amount <> 0 THEN
589          ozf_utility_pvt.calculate_functional_currency (
590                p_from_amount=>l_act_budgets_rec.request_amount
591               ,p_tc_currency_code=> l_act_budgets_rec.request_currency
592               ,p_ledger_id => p_ledger_id
593               ,x_to_amount=> l_approved_amount_fc
594               ,x_mrc_sob_type_code=> l_sob_type_code
595               ,x_fc_currency_code=> l_fc_code
596               ,x_exchange_rate_type=> l_exchange_rate_type
597               ,x_exchange_rate=> l_exchange_rate
598               ,x_return_status=> l_return_status
599             );
600          IF g_debug_flag = 'Y' THEN
601             ozf_utility_pvt.write_conc_log(l_full_name || 'calculate_functional_curr: ' || l_return_status);
602          END IF;
603 
604          IF l_return_status = fnd_api.g_ret_sts_error THEN
605             RAISE fnd_api.g_exc_error;
606          ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
607             RAISE fnd_api.g_exc_unexpected_error;
608          END IF;
609 
610       END IF;
611 
612       --nirprasa, ER 8399134 for transfer_type='UTILIZED' all three columns will be in
613       -- offer currency always.
614       OPEN c_offer_type(p_act_budgets_rec.act_budget_used_by_id);
615       FETCH c_offer_type INTO l_plan_currency;
616       CLOSE c_offer_type;
617 
618       IF g_debug_flag = 'Y' THEN
619          ozf_utility_pvt.write_conc_log(l_full_name || ' l_plan_currency: ' || l_plan_currency);
620          ozf_utility_pvt.write_conc_log(l_full_name || ' request_currency ' || l_act_budgets_rec.request_currency);
621       END IF;
622 
623       IF l_plan_currency <> l_act_budgets_rec.request_currency THEN
624       ozf_utility_pvt.convert_currency (x_return_status => x_return_status
625                                       ,p_from_currency => l_act_budgets_rec.request_currency
626                                       ,p_to_currency   => l_plan_currency
627                                       ,p_conv_type     => l_exchange_rate_type -- Added for bug 7030415
628                                       ,p_from_amount   => l_act_budgets_rec.request_amount
629                                       ,x_to_amount     => l_act_budgets_rec.approved_amount
630                                       ,x_rate          => l_rate
631                                       );
632 
633          l_act_budgets_rec.request_amount := l_act_budgets_rec.approved_amount;
634          l_act_budgets_rec.approved_original_amount := l_act_budgets_rec.approved_amount;
635       END IF;
636 
637 
638       OPEN c_act_util_rec (
639          p_act_budgets_rec.act_budget_used_by_id,
640          p_act_budgets_rec.arc_act_budget_used_by
641       );
642       FETCH c_act_util_rec INTO l_activity_id,
643                                 l_obj_ver_num,
644                                 l_old_approved_amount,
645                                 l_old_amount_fc;
646       CLOSE c_act_util_rec;
647 
648     -- nepanda Fix for bug 12911854
649     IF p_ledger_id IS NOT NULL THEN
650       OPEN c_get_gl_info(p_ledger_id);
651       FETCH c_get_gl_info INTO l_fc_currency_code;
652       CLOSE c_get_gl_info;
653       if l_fc_currency_code is not null then
654          l_approved_amount_fc := ozf_utility_pvt.currround(l_approved_amount_fc, l_fc_currency_code);
655       end if;
656     END IF;
657 
658     if l_act_budgets_rec.parent_src_curr is not null then
659        l_act_budgets_rec.parent_src_apprvd_amt := ozf_utility_pvt.currround(l_act_budgets_rec.parent_src_apprvd_amt, l_act_budgets_rec.parent_src_curr);
660     end if;
661 
662     IF l_approved_amount_fc = l_act_budgets_rec.request_amount THEN
663        if l_act_budgets_rec.request_currency is not null then
664           l_approved_amount_fc := ozf_utility_pvt.currround(l_act_budgets_rec.request_amount, l_act_budgets_rec.request_currency);
665        end if;
666     END IF ;
667 
668     if l_act_budgets_rec.request_currency is not null then
669        l_act_budgets_rec.request_amount := ozf_utility_pvt.currround(l_act_budgets_rec.request_amount, l_act_budgets_rec.request_currency);
670        l_act_budgets_rec.approved_amount := ozf_utility_pvt.currround(l_act_budgets_rec.approved_amount, l_act_budgets_rec.request_currency);
671     end if;
672 
673     --if act_budget record exist for this offer, update record.
674       IF l_activity_id IS NOT NULL THEN
675          UPDATE ozf_act_budgets
676          SET  request_amount = l_old_approved_amount + NVL(l_act_budgets_rec.request_amount, 0),
677               approved_amount =l_old_approved_amount + NVL(l_act_budgets_rec.request_amount, 0),
678               src_curr_request_amt =l_old_approved_amount + NVL(l_act_budgets_rec.request_amount, 0),
679               object_version_number = l_obj_ver_num + 1
680               ,parent_source_id = l_act_budgets_rec.parent_source_id
681               ,parent_src_curr  = l_act_budgets_rec.parent_src_curr
682               ,parent_src_apprvd_amt =l_act_budgets_rec.parent_src_apprvd_amt
683               ,approved_amount_fc = NVL(l_old_amount_fc,0) + NVL(l_approved_amount_fc,0)
684               ,approved_original_amount = l_old_approved_amount + l_act_budgets_rec.request_amount
685          WHERE activity_budget_id = l_activity_id
686              AND object_version_number = l_obj_ver_num;
687          x_act_budget_id := l_activity_id;
688 
689          IF (SQL%NOTFOUND) THEN
690             -- Error, check the msg level and added an error message to the
691             -- API message list
692             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
693                fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
694                fnd_msg_pub.ADD;
695             END IF;
696             RAISE fnd_api.g_exc_unexpected_error;
697          END IF;
698 
699          RETURN; -- exit from program.
700       END IF;
701 
702       IF l_act_budgets_rec.request_currency IS NULL THEN
703          ozf_utility_pvt.write_conc_log ('OZF_ACT_BUDG_NO_CURRENCY');
704          x_return_status            := fnd_api.g_ret_sts_error;
705       END IF;
706 
707 
708 
709       OPEN c_act_budget_id;
710       FETCH c_act_budget_id INTO l_act_budgets_rec.activity_budget_id;
711       CLOSE c_act_budget_id;
712 
713       l_requester_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
714 
715       INSERT INTO ozf_act_budgets
716                   (activity_budget_id,last_update_date
717                   ,last_updated_by, creation_date
718                   ,created_by,last_update_login -- other columns
719                   ,object_version_number,act_budget_used_by_id
720                   ,arc_act_budget_used_by,budget_source_type
721                   ,budget_source_id,transaction_type
722                   ,request_amount,request_currency
723                   ,request_date,user_status_id
724                   ,status_code,approved_amount
725                   ,approved_original_amount,approved_in_currency
726                   ,approval_date, approver_id
727                   ,spent_amount, partner_po_number
728                   ,partner_po_date, partner_po_approver
729                   ,posted_flag, adjusted_flag
730                   ,parent_act_budget_id, contact_id
731                   ,reason_code, transfer_type
732                   ,requester_id,date_required_by
733                   ,parent_source_id,parent_src_curr
734                   ,parent_src_apprvd_amt,partner_holding_type
735                   ,partner_address_id, vendor_id
736                   ,owner_id,recal_flag
737                   ,attribute_category, attribute1
738                   ,attribute2, attribute3
739                   ,attribute4, attribute5
740                   ,attribute6, attribute7
741                   ,attribute8, attribute9
742                   ,attribute10, attribute11
743                   ,attribute12, attribute13
744                   ,attribute14, attribute15
745                   ,approved_amount_fc
746                   ,src_curr_request_amt
747                   )
748            VALUES (l_act_budgets_rec.activity_budget_id,SYSDATE
749                    ,fnd_global.user_id, SYSDATE
750                    ,fnd_global.user_id, fnd_global.conc_login_id
751                    ,1, l_act_budgets_rec.act_budget_used_by_id
752                    ,l_act_budgets_rec.arc_act_budget_used_by, l_act_budgets_rec.budget_source_type
753                   ,l_act_budgets_rec.budget_source_id, l_act_budgets_rec.transaction_type
754                   ,l_act_budgets_rec.request_amount, l_act_budgets_rec.request_currency
755                   ,SYSDATE, l_act_budgets_rec.user_status_id
756                   ,NVL(l_act_budgets_rec.status_code, 'NEW'), l_act_budgets_rec.approved_amount
757                   ,l_act_budgets_rec.approved_amount,l_act_budgets_rec.approved_in_currency
758                   ,sysdate,l_requester_id
759                   ,l_act_budgets_rec.spent_amount, l_act_budgets_rec.partner_po_number
760                   ,l_act_budgets_rec.partner_po_date, l_act_budgets_rec.partner_po_approver
761                   ,l_act_budgets_rec.posted_flag, l_act_budgets_rec.adjusted_flag
762                   ,l_act_budgets_rec.parent_act_budget_id, l_act_budgets_rec.contact_id
763                   ,l_act_budgets_rec.reason_code, l_act_budgets_rec.transfer_type
764                   ,l_requester_id,l_act_budgets_rec.date_required_by
765                   ,l_act_budgets_rec.parent_source_id,l_act_budgets_rec.parent_src_curr
766                   ,l_act_budgets_rec.parent_src_apprvd_amt,l_act_budgets_rec.partner_holding_type
767                   ,l_act_budgets_rec.partner_address_id, l_act_budgets_rec.vendor_id
768                   ,NULL,l_act_budgets_rec.recal_flag
769                   ,l_act_budgets_rec.attribute_category, l_act_budgets_rec.attribute1
770                   ,l_act_budgets_rec.attribute2, l_act_budgets_rec.attribute3
771                   ,l_act_budgets_rec.attribute4, l_act_budgets_rec.attribute5
772                   ,l_act_budgets_rec.attribute6, l_act_budgets_rec.attribute7
773                   ,l_act_budgets_rec.attribute8, l_act_budgets_rec.attribute9
774                   ,l_act_budgets_rec.attribute10, l_act_budgets_rec.attribute11
775                   ,l_act_budgets_rec.attribute12, l_act_budgets_rec.attribute13
776                   ,l_act_budgets_rec.attribute14, l_act_budgets_rec.attribute15
777                   ,l_approved_amount_fc
778                   ,l_act_budgets_rec.approved_amount);
779 
780       x_act_budget_id := l_act_budgets_rec.activity_budget_id;
781 
782       IF g_debug_flag = 'Y' THEN
783          ozf_utility_pvt.write_conc_log(   l_api_name
784                                      || ': insert complete' || l_act_budgets_rec.activity_budget_id);
785       END IF;
786 
787           -- Standard call to get message count AND IF count is 1, get message info.
788       fnd_msg_pub.count_and_get (
789             p_count=> x_msg_count,
790             p_data=> x_msg_data,
791             p_encoded=> fnd_api.g_false
792       );
793 
794    EXCEPTION
795       WHEN fnd_api.g_exc_error THEN
796          ROLLBACK TO create_actbudgets_rec;
797          x_return_status            := fnd_api.g_ret_sts_error;
798          fnd_msg_pub.count_and_get (
799             p_count=> x_msg_count,
800             p_data=> x_msg_data,
801             p_encoded=> fnd_api.g_false
802          );
803 
804       WHEN fnd_api.g_exc_unexpected_error THEN
805          ROLLBACK TO create_actbudgets_rec;
806          x_return_status            := fnd_api.g_ret_sts_unexp_error;
807          fnd_msg_pub.count_and_get (
808             p_count=> x_msg_count,
809             p_data=> x_msg_data,
810             p_encoded=>fnd_api.g_false
811          );
812 
813       WHEN OTHERS THEN
814          ROLLBACK TO create_actbudgets_rec;
815          x_return_status            := fnd_api.g_ret_sts_unexp_error;
816 
817          fnd_msg_pub.count_and_get (
818             p_count=> x_msg_count,
819             p_data=> x_msg_data,
820             p_encoded=> fnd_api.g_false
821          );
822 
823    END create_actbudgets_rec;
824 
825   ---------------------------------------------------------------------
826 -- PROCEDURE
827 --    Create_Utilized_Rec
828 --
829 -- HISTORY
830 --    01/22/2003  feliu  Create.
831 --    10/14/2003  yzhao  Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
832 --    11/25/2003  yzhao  11.5.10 populate utilized_amt and earned_amt
833 ---------------------------------------------------------------------
834 
835    PROCEDURE create_utilized_rec (
836      x_return_status      OUT NOCOPY      VARCHAR2
837      ,x_msg_count          OUT NOCOPY      NUMBER
838      ,x_msg_data           OUT NOCOPY      VARCHAR2
839      ,x_utilization_id      OUT NOCOPY      NUMBER
840      ,p_utilization_rec    IN       ozf_fund_utilized_pvt.utilization_rec_type
841    ) IS
842       l_api_name            CONSTANT VARCHAR2 (30)     := 'create_utilized_rec';
843       l_full_name           CONSTANT VARCHAR2 (60)     :=    g_pkg_name || '.' || l_api_name;
844       l_return_status                VARCHAR2 (1);
845       l_utilization_rec              ozf_fund_utilized_pvt.utilization_rec_type := p_utilization_rec;
846       l_earned_amt                   NUMBER;
847       l_obj_num                      NUMBER;
848       l_fund_type                    VARCHAR2 (30);
849       l_parent_fund_id               NUMBER;
850       l_accrual_basis                VARCHAR2 (30);
851       l_original_budget              NUMBER;
852       l_event_id                     NUMBER;
853       /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
854       l_mc_record_id                 NUMBER;
855       l_mc_obj_num                   NUMBER;
856       l_mc_col_1                     NUMBER;
857       l_mc_col_6                     NUMBER;
858       l_mc_col_7                     NUMBER;
859       l_mc_col_8                     NUMBER;
860       l_mc_col_9                     NUMBER;
861        */
862       l_offer_type                   VARCHAR2 (30);
863       l_accrual_flag                 VARCHAR2 (1);
864       l_set_of_book_id               NUMBER;
865       l_sob_type_code                VARCHAR2 (30);
866       l_fc_code                      VARCHAR2 (150);
867       l_fund_rec                     ozf_funds_pvt.fund_rec_type;
868       l_rollup_orig_amt           NUMBER;
869       l_rollup_earned_amt         NUMBER;
870       l_new_orig_amt              NUMBER;
871       l_new_utilized_amt          NUMBER;
872       l_new_earned_amt            NUMBER;
873       l_rate                      NUMBER;
874       l_univ_amt                  NUMBER;
875       l_new_paid_amt              NUMBER;
876       l_new_univ_amt              NUMBER;
877       l_paid_amt                  NUMBER;
878       l_rollup_paid_amt           NUMBER;
879       l_committed_amt             NUMBER;
880       l_rollup_committed_amt      NUMBER;
881       -- yzhao: 10/14/2003 added
882       l_new_committed_amt         NUMBER;
883       l_new_recal_committed       NUMBER;
884       l_recal_committed           NUMBER;
885       l_rollup_recal_committed    NUMBER;
886       l_plan_id                   NUMBER;
887       l_act_budget_id             NUMBER;
888       l_act_budget_objver         NUMBER;
889       l_liability_flag            VARCHAR2(1);
890       -- yzhao: 11.5.10
891       l_utilized_amt              NUMBER;
892       l_rollup_utilized_amt       NUMBER;
893       l_off_invoice_gl_post_flag  VARCHAR2(1);
894       l_order_ledger              NUMBER;
895       l_ord_ledger_name           VARCHAR2(150);
896       l_fund_ledger               NUMBER;
897       l_custom_setup_id           NUMBER;
898       l_beneficiary_account_id    NUMBER;
899       l_req_header_id             NUMBER;
900       -- rimehrot: added for R12
901       l_plan_currency                VARCHAR2 (150);
902       l_transaction_currency         VARCHAR2 (150);
903       l_objfundsum_rec               ozf_objfundsum_pvt.objfundsum_rec_type := NULL;
904       l_objfundsum_id                NUMBER;
905       l_offer_id                     NUMBER;
906 
907       --nirprasa
908       l_autopay_party_attr       VARCHAR2(30);
909       l_autopay_party_id         NUMBER;
910 
911 --Added variable for bug 6278466
912       l_org_id                    NUMBER; -- removed initialization for bug 6278466
913 
914 --Added c_site_org_id for bug 6278466
915       CURSOR c_site_org_id (p_site_use_id IN NUMBER) IS
916          SELECT org_id
917            FROM hz_cust_site_uses_all
918           WHERE site_use_id = p_site_use_id;
919 
920       -- Cursor to get the sequence for utilization_id
921       CURSOR c_utilization_seq IS
922          SELECT ozf_funds_utilized_s.NEXTVAL
923          FROM DUAL;
924 
925       -- Cursor to get fund earned amount and object_version_number
926       CURSOR c_fund_b (p_fund_id IN NUMBER) IS
927          SELECT object_version_number
928                ,accrual_basis
929                ,fund_type
930                ,original_budget
931                ,earned_amt
932                ,paid_amt
933                ,parent_fund_id
934                ,rollup_original_budget
935                ,rollup_earned_amt
936                ,rollup_paid_amt
937                -- yzhao 10/14/2003 added below
938                ,committed_amt
939                ,recal_committed
940                ,rollup_committed_amt
941                ,rollup_recal_committed
942                ,plan_id
943                ,NVL(liability_flag, 'N')
944                -- yzhao: 11.5.10
945                ,utilized_amt
946                ,rollup_utilized_amt
947          FROM ozf_funds_all_b
948          WHERE fund_id = p_fund_id;
949 
950       /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
951       CURSOR c_mc_trans(p_fund_id IN NUMBER) IS
952          SELECT mc_record_id
953                 ,object_version_number
954                 ,amount_column1 -- original
955                 ,amount_column6 -- committed; yzhao: 10/14/2003 added
956                 ,amount_column7 -- earn
957                 ,amount_column8 -- paid
958         ,amount_column9 -- utilized
959          FROM ozf_mc_transactions_all
960          WHERE source_object_name ='FUND'
961          AND source_object_id = p_fund_id;
962        */
963 
964       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
965          SELECT offer_type, custom_setup_id, beneficiary_account_id,
966                 nvl(transaction_currency_code,fund_request_curr_code) offer_currency_code,
967                 transaction_currency_code,
968                 offer_id,autopay_party_attr,autopay_party_id --nirprasa
969          FROM   ozf_offers
970          WHERE  qp_list_header_id = p_offer_id;
971 
972       CURSOR c_accrual_flag (p_price_adjustment_id IN NUMBER) IS
973          SELECT NVL(accrual_flag,'N')
974          FROM oe_price_adjustments
975          WHERE price_Adjustment_id = p_price_Adjustment_id;
976 
977       CURSOR c_parent (p_fund_id IN NUMBER)IS
978          SELECT fund_id
979                ,object_version_number
980                ,rollup_original_budget
981                ,rollup_earned_amt
982                ,rollup_paid_amt
983                -- yzhao: 10/14/2003 added
984                ,rollup_committed_amt
985                ,rollup_recal_committed
986                -- yzhao: 11.5.10
987                ,rollup_utilized_amt
988          FROM ozf_funds_all_b
989          connect by prior  parent_fund_id =fund_id
990          start with fund_id =  p_fund_id;
991 
992       /* 10/14/2003  yzhao  Fix TEVA bug - customer fully accrual budget committed amount is always 0
993                        update ozf_act_budgets REQUEST between fully accrual budget and its offer when accrual happens
994        */
995       CURSOR c_accrual_budget_reqeust(p_fund_id IN NUMBER, p_plan_id IN NUMBER) IS
996          SELECT activity_budget_id
997              , object_version_number
998          FROM   ozf_act_budgets
999          WHERE  arc_act_budget_used_by = 'OFFR'
1000          AND    act_budget_used_by_id = p_plan_id
1001          AND    budget_source_type = 'FUND'
1002          AND    budget_source_id = p_fund_id
1003          AND    transfer_type = 'REQUEST'
1004          AND    status_code = 'APPROVED';
1005 
1006       CURSOR c_budget_request_utilrec(p_fund_id IN NUMBER, p_plan_id IN NUMBER, p_actbudget_id IN NUMBER) IS
1007          SELECT utilization_id
1008                 , object_version_number
1009          FROM   ozf_funds_utilized_all_b
1010          WHERE  utilization_type = 'REQUEST'
1011          AND    fund_id = p_fund_id
1012          AND    plan_type = 'FUND'
1013          AND    plan_id = p_fund_id
1014          AND    component_type = 'OFFR'
1015          AND    component_id = p_plan_id
1016          AND    ams_activity_budget_id = p_actbudget_id;
1017 
1018      /*fix for bug 4778995
1019      -- yzhao: 11.5.10 get time_id
1020      CURSOR c_get_time_id(p_date IN DATE) IS
1021         SELECT month_id, ent_qtr_id, ent_year_id
1022         FROM   ozf_time_day
1023         WHERE  report_date = trunc(p_date);
1024      */
1025 
1026 
1027      /* Add by feliu on 12/30/03 to fix org issue:
1028         If order org's SOB is different than Budget Org's SOB, then we use Budget's org_id and function currency.
1029     and have log message to ask use to make manual adjustment.otherwise we use order org_id and function currency.
1030       kdass 08/23/2005 MOAC change: changed comparison from SOB to Ledger
1031       */
1032       /*
1033       CURSOR c_order_sob(p_org_id IN NUMBER) IS
1034         SELECT SET_OF_BOOKS_ID
1035         FROM ozf_sys_parameters_all
1036         WHERE org_id = p_org_id;
1037 
1038       -- yzhao: 11.5.10 check if post to gl for off invoice discount
1039       CURSOR c_fund_sob(p_fund_id IN NUMBER) IS
1040         SELECT  sob.set_of_books_id, fun.ORG_id, NVL(sob.gl_acct_for_offinv_flag, 'F')
1041         FROM    ozf_sys_parameters_all sob
1042                ,ozf_funds_all_b  fun
1043         WHERE fun.fund_id = p_fund_id
1044         AND   sob.org_id = fun.ORG_id ;
1045       */
1046 
1047       --nirprasa, for bug 7654383. removed fund's org_id
1048       CURSOR c_fund_ledger(p_fund_id IN NUMBER) IS
1049          SELECT  fun.ledger_id
1050          FROM    gl_sets_of_books sob,
1051                  ozf_funds_all_b fun
1052          where  sob.set_of_books_id = fun.ledger_id
1053          and fun.fund_id = p_fund_id;
1054 
1055       CURSOR c_offinv_flag(p_org_id IN NUMBER) IS
1056          SELECT  NVL(sob.gl_acct_for_offinv_flag, 'F')
1057          FROM    ozf_sys_parameters_all sob
1058          WHERE   sob.org_id = p_org_id;
1059 
1060       -- yzhao: 11.5.10 populate reference_type/id for special pricing
1061       CURSOR c_get_request_header_id(p_list_header_id IN NUMBER) IS
1062          SELECT request_header_id
1063          FROM   ozf_request_headers_all_b
1064          WHERE  offer_id =p_list_header_id;
1065 
1066      -- rimehrot: for R12 update ozf_object_fund_summary table
1067       CURSOR c_get_objfundsum_rec(p_object_type IN VARCHAR2, p_object_id IN NUMBER, p_fund_id IN NUMBER) IS
1068          SELECT objfundsum_id
1069               , object_version_number
1070               , committed_amt
1071               , recal_committed_amt
1072               , utilized_amt
1073               , earned_amt
1074               , paid_amt
1075               , plan_curr_committed_amt
1076               , plan_curr_recal_committed_amt
1077               , plan_curr_utilized_amt
1078               , plan_curr_earned_amt
1079               , plan_curr_paid_amt
1080               , univ_curr_committed_amt
1081               , univ_curr_recal_committed_amt
1082               , univ_curr_utilized_amt
1083               , univ_curr_earned_amt
1084               , univ_curr_paid_amt
1085          FROM   ozf_object_fund_summary
1086          WHERE  object_type = p_object_type
1087          AND    object_id = p_object_id
1088          AND    fund_id = p_fund_id;
1089 
1090 --Ship - Debit Enhancements / Added by Pranay
1091       CURSOR c_sd_request_header_id(p_list_header_id IN NUMBER) IS
1092          SELECT request_header_id
1093          FROM   ozf_sd_request_headers_all_b
1094          WHERE  offer_id =p_list_header_id;
1095 
1096 -- nirprasa, cursor for currency conversion type.
1097       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
1098          SELECT exchange_rate_type
1099          FROM   ozf_sys_parameters_all
1100          WHERE  org_id = p_org_id;
1101 
1102       --kdass - bug 9470625
1103       --if formula is specified on offer line, then operand in oe_price_adjustments is not correct,
1104       --query it from qp_list_lines table
1105       CURSOR c_sd_offer_discount (p_price_adjustment_id IN NUMBER) IS
1106          SELECT NVL2(qpll.price_by_formula_id, qpll.operand, oe.operand),
1107                 oe.arithmetic_operator
1108            FROM oe_price_adjustments oe, qp_list_lines qpll
1109           WHERE oe.price_adjustment_id = p_price_adjustment_id
1110             AND oe.list_line_id = qpll.list_line_id;
1111 
1112         --fix for bug 13742169
1113         -- pass header_id to resolve perf issue
1114         CURSOR c_is_parent_line(p_header_id IN NUMBER,
1115                                        p_line_id IN NUMBER) IS
1116         SELECT 1
1117         FROM oe_order_lines_all
1118         WHERE header_id = p_header_id
1119          AND split_from_line_id = p_line_id;
1120 
1121         CURSOR c_utilization_id (p_line_id IN NUMBER, p_object_id IN NUMBER,
1122                                          p_object_type IN VARCHAR2, p_plan_id IN NUMBER,
1123                                          p_inventory_item_id IN NUMBER,
1124                                          p_price_adjustment_id IN NUMBER) IS
1125         SELECT utilization_id, object_version_number
1126         FROM ozf_funds_utilized_all_b
1127         WHERE order_line_id = p_line_id
1128         AND object_id = p_object_id
1129         AND object_type = p_object_type
1130         AND plan_id = p_plan_id
1131         AND product_id = p_inventory_item_id
1132         AND price_adjustment_id = p_price_adjustment_id
1133         AND gl_posted_flag = 'N';
1134 
1135        --Fix for Bug 12657908
1136       CURSOR c_get_year_id(p_gl_date IN DATE) IS
1137         SELECT ent_year_id
1138         FROM OZF_TIME_ENT_YEAR ey
1139         WHERE p_gl_date between ey.start_date and ey.end_date;
1140 
1141 
1142       c_purchase_price purchase_price_cursor_type;
1143       l_column_name VARCHAR2(15);
1144       l_is_parent_line  NUMBER;
1145       l_utilization_id        NUMBER;
1146       l_obj_ver_num        NUMBER;
1147 
1148    BEGIN
1149       --------------------- initialize -----------------------
1150       SAVEPOINT create_utilized_rec;
1151       IF g_debug_flag = 'Y' THEN
1152          ozf_utility_pvt.write_conc_log(   l_full_name
1153                                      || ': start' || p_utilization_rec.utilization_type);
1154       END IF;
1155 
1156       x_return_status            := fnd_api.g_ret_sts_success;
1157 
1158       --Bug 13463758 Decide if it is partial shipment/backorder/split
1159       --scenario and skip to update instead of insert.
1160       -- Update ozf_funds_utilized_allb_
1161       -- Let the same insert flow take care of other tables.
1162 
1163       IF g_debug_flag = 'Y' THEN
1164         ozf_utility_pvt.write_conc_log ('order_line_id ' || l_utilization_rec.order_line_id);
1165       END IF;
1166 
1167       l_is_parent_line := NULL;
1168 
1169       OPEN c_is_parent_line(l_utilization_rec.object_id,
1170                                      l_utilization_rec.order_line_id);
1171       FETCH c_is_parent_line INTO l_is_parent_line;
1172       CLOSE c_is_parent_line;
1173 
1174       l_utilization_id := NULL;
1175       l_obj_ver_num := NULL;
1176 
1177       IF g_debug_flag = 'Y' THEN
1178         ozf_utility_pvt.write_conc_log ('l_is_parent_line ' || l_is_parent_line);
1179         ozf_utility_pvt.write_conc_log ('order_line_id ' || l_utilization_rec.order_line_id);
1180         ozf_utility_pvt.write_conc_log ('object_id ' || l_utilization_rec.object_id);
1181         ozf_utility_pvt.write_conc_log ('object_type ' || l_utilization_rec.object_type);
1182         ozf_utility_pvt.write_conc_log ('plan_id ' || l_utilization_rec.component_id);
1183         ozf_utility_pvt.write_conc_log ('inventory_item_id ' || l_utilization_rec.product_id);
1184         ozf_utility_pvt.write_conc_log ('price_adjustment_id ' || l_utilization_rec.price_adjustment_id);
1185       END IF;
1186 
1187       IF NVL(l_is_parent_line,0) = 1 THEN
1188               OPEN c_utilization_id(l_utilization_rec.order_line_id,
1189                                            l_utilization_rec.object_id,
1190                                            l_utilization_rec.object_type,
1191                                            l_utilization_rec.component_id,
1192                                            l_utilization_rec.product_id,
1193                                            l_utilization_rec.price_adjustment_id);
1194               FETCH c_utilization_id INTO l_utilization_id, l_obj_ver_num;
1195               CLOSE c_utilization_id;
1196       END IF;
1197 
1198       IF g_debug_flag = 'Y' THEN
1199         ozf_utility_pvt.write_conc_log ('l_utilization_id ' || l_utilization_id);
1200         ozf_utility_pvt.write_conc_log ('l_obj_ver_num ' || l_obj_ver_num);
1201       END IF;
1202 
1203        -- Get the identifier
1204       IF l_utilization_id IS NOT NULL THEN
1205           l_utilization_rec.utilization_id := l_utilization_id;
1206       ELSE
1207           OPEN c_utilization_seq;
1208           FETCH c_utilization_seq INTO l_utilization_rec.utilization_id;
1209           CLOSE c_utilization_seq;
1210       END IF;
1211 
1212       OPEN c_fund_b (l_utilization_rec.fund_id);
1213       FETCH c_fund_b INTO l_obj_num
1214                          ,l_accrual_basis
1215                          ,l_fund_type
1216                          ,l_original_budget
1217                          ,l_earned_amt
1218                          ,l_paid_amt
1219                          ,l_parent_fund_id
1220                          ,l_rollup_orig_amt
1221                          ,l_rollup_earned_amt
1222                          ,l_rollup_paid_amt
1223                          ,l_committed_amt
1224                          ,l_recal_committed
1225                          ,l_rollup_committed_amt
1226                          ,l_rollup_recal_committed
1227                          ,l_plan_id
1228                          ,l_liability_flag
1229                          ,l_utilized_amt
1230                          ,l_rollup_utilized_amt;
1231       IF (c_fund_b%NOTFOUND) THEN
1232          CLOSE c_fund_b;
1233          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1234             fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1235             fnd_msg_pub.ADD;
1236          END IF;
1237          RAISE fnd_api.g_exc_error;
1238       END IF;
1239       CLOSE c_fund_b;
1240 
1241       OPEN c_offinv_flag(l_utilization_rec.org_id);
1242       FETCH c_offinv_flag INTO l_off_invoice_gl_post_flag;
1243       CLOSE c_offinv_flag;
1244 
1245       --kdass MOAC changes: change comparison from SOB to Ledger
1246       /*
1247       OPEN c_order_sob(l_utilization_rec.org_id);
1248       FETCH c_order_sob INTO l_order_sob;
1249       CLOSE c_order_sob;
1250 
1251       OPEN c_fund_sob(l_utilization_rec.fund_id);
1252       FETCH c_fund_sob INTO l_fund_sob, l_fund_org, l_off_invoice_gl_post_flag;
1253       CLOSE c_fund_sob;
1254       */
1255 
1256       OPEN c_fund_ledger(l_utilization_rec.fund_id);
1257       FETCH c_fund_ledger INTO l_fund_ledger;
1258       CLOSE c_fund_ledger;
1259       --get the order's ledger id
1260       mo_utils.Get_Ledger_Info (p_operating_unit => l_utilization_rec.org_id
1261                                ,p_ledger_id      => l_order_ledger
1262                                ,p_ledger_name    => l_ord_ledger_name);
1263       IF l_utilization_rec.org_id IS NULL THEN
1264          IF g_debug_flag = 'Y' THEN
1265             ozf_utility_pvt.write_conc_log (' org_id from order is null ');
1266          END IF;
1267       ELSE
1268          IF g_debug_flag = 'Y' THEN
1269             ozf_utility_pvt.write_conc_log (' org_id from order: ' || l_utilization_rec.org_id);
1270          END IF;
1271       END IF;
1272 
1273       IF l_fund_ledger IS NOT NULL AND l_order_ledger <> l_fund_ledger THEN
1274          -- l_utilization_rec.org_id := l_fund_org;  R12: stick to order's org. Budget org is not essential information
1275          ozf_utility_pvt.write_conc_log (' Warning: There is a potential problem with this accrual record. The ledger ');
1276          ozf_utility_pvt.write_conc_log ('used by Trade Management to create the GL postings for this ');
1277          ozf_utility_pvt.write_conc_log ('accrual does not match the one the sales order rolls up to. Please ');
1278          ozf_utility_pvt.write_conc_log ('review carefully and make adjustments in Trade Management if necessary.');
1279       END IF;
1280 
1281       -- Added for bug 7030415, moved the the code here to get the correct utilization org_id.
1282 
1283       OPEN c_offer_type(l_utilization_rec.component_id);
1284       FETCH c_offer_type INTO l_offer_type, l_custom_setup_id, l_beneficiary_account_id, l_plan_currency,
1285                               l_transaction_currency,l_offer_id,l_autopay_party_attr,l_autopay_party_id;
1286       CLOSE c_offer_type;
1287 
1288       IF g_debug_flag = 'Y' THEN
1289          ozf_utility_pvt.write_conc_log ('l_offer_type: ' || l_offer_type);
1290          ozf_utility_pvt.write_conc_log ('l_offer_id: ' || l_offer_id);
1291          ozf_utility_pvt.write_conc_log ('l_utilization_rec.billto_cust_account_id: ' || l_utilization_rec.billto_cust_account_id);
1292          ozf_utility_pvt.write_conc_log ('l_utilization_rec.order_line_id: ' || l_utilization_rec.order_line_id);
1293       END IF;
1294 
1295       -- added by feliu on 08/30/2005 for R12.
1296       IF l_offer_type = 'VOLUME_OFFER' THEN
1297          l_beneficiary_account_id := ozf_volume_calculation_pub.get_beneficiary(l_offer_id
1298                                                                             ,l_utilization_rec.order_line_id);
1299          --04-MAY-09 kdass bug 8421406 - passed order_line_id to get volume offer beneficiary
1300          IF l_beneficiary_account_id = 0 THEN
1301             l_utilization_rec.cust_account_id := l_utilization_rec.billto_cust_account_id;
1302          ELSE
1303             l_utilization_rec.cust_account_id := l_beneficiary_account_id;
1304             --kdass bug 12912760 - populate billto_cust_account_id with Order customer
1305             --l_utilization_rec.billto_cust_account_id := NULL;
1306             l_utilization_rec.ship_to_site_use_id := NULL;
1307             l_utilization_rec.bill_to_site_use_id := NULL;
1308          END IF;
1309 
1310          IF g_debug_flag = 'Y' THEN
1311             ozf_utility_pvt.write_conc_log ('l_utilization_rec.cust_account_id ' || l_utilization_rec.cust_account_id);
1312             ozf_utility_pvt.write_conc_log ('l_utilization_rec.billto_cust_account_id: ' || l_utilization_rec.billto_cust_account_id);
1313          END IF;
1314 
1315       ELSE
1316 
1317       -- yzhao: 11.5.10 populate cust_account_id with offer's beneficiary account, otherwise billto cust account id
1318         IF l_utilization_rec.cust_account_id IS NULL THEN
1319          IF l_beneficiary_account_id IS NOT NULL THEN
1320 
1321             --Added c_site_org_id for bug 6278466
1322             IF l_autopay_party_attr <> 'CUSTOMER' THEN
1323               OPEN c_site_org_id(l_autopay_party_id);
1324               FETCH c_site_org_id INTO l_org_id;
1325               CLOSE c_site_org_id;
1326               l_utilization_rec.org_id := l_org_id;
1327             END IF;
1328             l_utilization_rec.cust_account_id := l_beneficiary_account_id;
1329 
1330             --kdass bug 8258508/ Duplicate bill to sites for same cust_account_id. Cases are as follows:
1331             --Defaulting bill_to_site_id from beneficiary of type CUSTOMER_BILL_TO
1332             --Defaulting ship_to from beneficiary of type SHIP_TO
1333             --No bill_to/ship_to for beneficiary of type CUSTOMER
1334             IF l_autopay_party_attr = 'CUSTOMER_BILL_TO' THEN
1335                 l_utilization_rec.bill_to_site_use_id := l_autopay_party_id;
1336                 l_utilization_rec.ship_to_site_use_id := NULL;
1337             ELSIF l_autopay_party_attr = 'SHIP_TO' THEN
1338                 l_utilization_rec.bill_to_site_use_id := NULL;
1339                 l_utilization_rec.ship_to_site_use_id := l_autopay_party_id;
1340             ELSIF l_autopay_party_attr = 'CUSTOMER' THEN
1341                 l_utilization_rec.bill_to_site_use_id := NULL;
1342                 l_utilization_rec.ship_to_site_use_id := NULL;
1343             END IF;
1344 
1345             IF g_debug_flag = 'Y' THEN
1346                ozf_utility_pvt.write_conc_log ('l_utilization_rec.bill_to_site_use_id: ' || l_utilization_rec.bill_to_site_use_id);
1347                ozf_utility_pvt.write_conc_log ('l_utilization_rec.ship_to_site_use_id: ' || l_utilization_rec.ship_to_site_use_id);
1348             END IF;
1349 
1350          ELSE
1351             l_utilization_rec.cust_account_id := l_utilization_rec.billto_cust_account_id;
1352          END IF;
1353         END IF;
1354       END IF;
1355 
1356 
1357         /* Added for bug 7030415,- get the exchange rate based on org_id and pass it to the currency conversion API
1358         Utilization amount is converted from utilization curr to functional curr to populate
1359         acctd_amount column of utilization table.*/
1360 
1361 
1362         OPEN c_get_conversion_type(l_utilization_rec.org_id);
1363         FETCH c_get_conversion_type INTO l_utilization_rec.exchange_rate_type;
1364         CLOSE c_get_conversion_type;
1365 
1366         --nepanda Fix for bug 8994266 : commented IF to call calculate_functional_currency in case of amount = 0 also
1367       --IF l_utilization_rec.amount <> 0 THEN
1368          l_utilization_rec.amount := ozf_utility_pvt.currround(l_utilization_rec.amount , l_utilization_rec.currency_code);  -- round amount to fix bug 3615680;
1369 
1370          --nirprasa, ER 8399134
1371          l_utilization_rec.plan_curr_amount := ozf_utility_pvt.currround(l_utilization_rec.plan_curr_amount , l_utilization_rec.plan_currency_code);  -- round amount to fix bug 3615680;
1372          IF g_debug_flag = 'Y' THEN
1373            ozf_utility_pvt.write_conc_log('**************************START****************************');
1374            ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_utilization_rec.plan_curr_amount );
1375            ozf_utility_pvt.write_conc_log(l_api_name||' From Curr: '||l_utilization_rec.plan_currency_code );
1376            ozf_utility_pvt.write_conc_log(l_api_name||' p_ledger_id: '|| l_order_ledger);
1377            ozf_utility_pvt.write_conc_log(l_api_name||' l_utilization_rec.exchange_rate_type: '|| l_utilization_rec.exchange_rate_type);
1378            ozf_utility_pvt.write_conc_log('Utilization amount is converted from transactional curr to functional curr to populate acctd_amount column');
1379         END IF;
1380          --plan_currency_code =  offers currency, if its Arrows case of diff offer and budget currency
1381          --else plan_currency_code = order currency, if its Null currency offer case
1382          ozf_utility_pvt.calculate_functional_currency (
1383                   p_from_amount=> l_utilization_rec.plan_curr_amount --12.2, multi-currency enhancement
1384                  ,p_tc_currency_code=> l_utilization_rec.plan_currency_code --12.2, multi-currency enhancement
1385                  ,p_ledger_id => l_order_ledger
1386                  ,x_to_amount=> l_utilization_rec.acctd_amount
1387                  ,x_mrc_sob_type_code=> l_sob_type_code
1388                  ,x_fc_currency_code=> l_fc_code
1389                  ,x_exchange_rate_type=> l_utilization_rec.exchange_rate_type
1390                  ,x_exchange_rate=> l_utilization_rec.exchange_rate
1391                  ,x_return_status=> l_return_status
1392                );
1393 
1394          IF l_return_status = fnd_api.g_ret_sts_error THEN
1395             RAISE fnd_api.g_exc_error;
1396          ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1397             RAISE fnd_api.g_exc_unexpected_error;
1398          END IF;
1399      -- END IF; --nepanda Fix for bug 8994266
1400 
1401       -- yzhao: 10/20/2003 when object sources from sales accrual budget, the budget behaves like fixed budget.
1402       IF l_fund_type = 'FULLY_ACCRUED' AND
1403          l_utilization_rec.component_type = 'OFFR' AND
1404          l_plan_id <> l_utilization_rec.component_id  THEN
1405          l_fund_type := 'FIXED' ;
1406       END IF;
1407 
1408       IF g_debug_flag = 'Y' THEN
1409       ozf_utility_pvt.write_conc_log(l_api_name||' l_fc_code '|| l_fc_code );
1410       ozf_utility_pvt.write_conc_log(l_api_name||' l_plan_currency '|| l_plan_currency );
1411       END IF;
1412 
1413       --nirprasa, ER 8399134 multi-currency enhancement, l_plan_currency = offer currency
1414       --l_utilization_rec.plan_currency_code = transactional currency
1415       --This is added for null curr offers to convert amount from order to offer's
1416       -- fund request currency code(JTF_DEFAULT_CURENCY_CODE) currency
1417 
1418       IF l_transaction_currency IS NULL THEN
1419         IF l_plan_currency = l_fc_code THEN
1420            l_utilization_rec.fund_request_amount := l_utilization_rec.acctd_amount;
1421         ELSIF l_plan_currency = l_utilization_rec.currency_code THEN
1422            l_utilization_rec.fund_request_amount := l_utilization_rec.amount;
1423         ELSIF l_utilization_rec.fund_request_amount IS NULL OR
1424         l_utilization_rec.fund_request_amount = FND_API.G_MISS_NUM THEN
1425         --need to chk this for cancel/partialship and returned orders
1426         --where this amount will already be populated.
1427         ozf_utility_pvt.convert_currency (x_return_status => x_return_status
1428               ,p_from_currency => l_utilization_rec.plan_currency_code
1429               ,p_to_currency   => l_plan_currency
1430               ,p_conv_type     => l_utilization_rec.exchange_rate_type -- Added for bug 7030415
1431               ,p_from_amount   => l_utilization_rec.plan_curr_amount
1432               ,x_to_amount     => l_utilization_rec.fund_request_amount
1433               ,x_rate          => l_rate);
1434         END IF;
1435 
1436       ELSE
1437         l_utilization_rec.fund_request_amount := l_utilization_rec.plan_curr_amount;
1438       END IF;
1439       l_utilization_rec.fund_request_currency_code := l_plan_currency;
1440       IF l_fund_type = 'FIXED' THEN
1441       ---- kpatro 11/09/2006 added check for utilization_type to fix 5523042
1442       IF  l_utilization_rec.utilization_type IS NULL THEN
1443          IF l_offer_type IN ('ACCRUAL') THEN
1444             l_utilization_rec.utilization_type := 'ACCRUAL';
1445             l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1446             l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1447             l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1448             l_utilization_rec.fund_request_amount_remaining := l_utilization_rec.fund_request_amount;
1449          ELSIF l_offer_type IN( 'DEAL','VOLUME_OFFER') THEN
1450             l_accrual_flag :='N';
1451             OPEN c_accrual_flag( l_utilization_rec.price_adjustment_id ) ;
1452             FETCH c_accrual_flag INTO l_accrual_flag ;
1453             CLOSE c_accrual_flag ;
1454             IF l_accrual_flag = 'Y' THEN
1455                l_utilization_rec.utilization_type := 'ACCRUAL';
1456                l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1457                l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1458                l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1459                l_utilization_rec.fund_request_amount_remaining := l_utilization_rec.fund_request_amount;
1460             ELSE
1461                l_utilization_rec.utilization_type := 'UTILIZED';
1462             END IF;
1463          ELSE
1464             l_utilization_rec.utilization_type := 'UTILIZED';
1465          END IF;
1466         END IF;
1467          -- 11.5.10: for off-invoice offer, if posting to gl flag is off, set gl_posted_flag to null so it shows up in earned and paid
1468          --          if flag is on, leave the flag as 'N'
1469          IF l_utilization_rec.utilization_type = 'UTILIZED'
1470          --AND l_off_invoice_gl_post_flag = 'F'
1471          THEN
1472            -- l_utilization_rec.gl_posted_flag := G_GL_FLAG_NULL;  -- null;
1473          --ELSE
1474             IF l_utilization_rec.gl_posted_flag IS NULL THEN  -- added by feliu on 06/09/04
1475                l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;      -- 'N', waiting for posting to gl
1476             END IF;
1477 
1478             IF l_utilization_rec.gl_posted_flag = G_GL_FLAG_NO
1479             AND l_utilization_rec.utilization_type IN ( 'ACCRUAL' ,'ADJUSTMENT') THEN
1480                l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1481                l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1482                l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1483                l_utilization_rec.fund_request_amount_remaining := l_utilization_rec.fund_request_amount;
1484             END IF;
1485          ELSE -- Added by nirprasa, This is added for partial shipment scenario when amt_reminain was being updated as null.
1486              IF l_utilization_rec.gl_posted_flag IS NULL THEN  -- added by feliu on 06/09/04
1487                 l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;      -- 'N', waiting for posting to gl
1488              END IF;
1489              IF l_utilization_rec.gl_posted_flag = G_GL_FLAG_NO AND l_utilization_rec.utilization_type IN ( 'ACCRUAL' ,'ADJUSTMENT') THEN
1490                  l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1491                  l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1492                  l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1493                  l_utilization_rec.fund_request_amount_remaining := l_utilization_rec.fund_request_amount;
1494              END IF;
1495          END IF;
1496       ELSE
1497          IF l_accrual_basis = 'SALES' THEN
1498             l_utilization_rec.utilization_type := 'SALES_ACCRUAL';
1499             l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;-- set to 'X' only after shipping.
1500          ELSIF l_accrual_basis = 'CUSTOMER' THEN
1501             l_utilization_rec.utilization_type := 'ACCRUAL';
1502             -- yzhao: fix bug 3435420 - do not post to gl for customer accrual budget with liability off
1503             IF l_liability_flag = 'Y' THEN
1504                l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1505                l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1506                l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1507                l_utilization_rec.fund_request_amount_remaining := l_utilization_rec.fund_request_amount;
1508                IF l_utilization_rec.gl_posted_flag IS NULL THEN  -- yzhao 06/10/04
1509                    l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;      -- 'N', waiting for posting to gl
1510                END IF;
1511             ELSE
1512                l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;--G_GL_FLAG_NOLIAB;  -- 'X', do not post to gl
1513             END IF;
1514          END IF;
1515       END IF;
1516 
1517       --// Bug Fix 10037158
1518       IF l_offer_type = 'TERMS' THEN
1519          l_utilization_rec.gl_posted_flag := G_GL_FLAG_NOLIAB;  -- For Terms Upgrade offer 'X', do not post to gl
1520       END IF;
1521 
1522       l_utilization_rec.plan_id       := l_utilization_rec.component_id;
1523       l_utilization_rec.plan_type       := 'OFFR';
1524       l_utilization_rec.component_type       := 'OFFR';
1525       l_utilization_rec.adjustment_desc := fnd_message.get_string ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK');
1526 
1527       -- yzhao: 11/25/2003 11.5.10 populate adjustment_date and time_id
1528       IF l_utilization_rec.adjustment_date IS NULL THEN
1529          l_utilization_rec.adjustment_date := SYSDATE;
1530       END IF;
1531 
1532       /*fix for bug 4778995
1533       OPEN c_get_time_id(l_utilization_rec.adjustment_date);
1534       FETCH c_get_time_id INTO l_utilization_rec.month_id, l_utilization_rec.quarter_id, l_utilization_rec.year_id;
1535       CLOSE c_get_time_id;
1536       */
1537 
1538 
1539       /* yzhao: 11.5.10 populate reference_type/id for special pricing
1540                 seeded custom_setup_id for special pricing:
1541                 115 offer invoice
1542                 116 accrual
1543                 117 scan data
1544       */
1545       IF l_utilization_rec.reference_id IS NULL AND l_custom_setup_id IN (115, 116, 117) THEN
1546          OPEN c_get_request_header_id(l_utilization_rec.component_id);
1547          FETCH c_get_request_header_id INTO l_utilization_rec.reference_id;
1548          CLOSE c_get_request_header_id;
1549          l_utilization_rec.reference_type := 'SPECIAL_PRICE';
1550       END IF;
1551 
1552       --Ship - Debit enhancements / Added by Pranay
1553       IF l_utilization_rec.reference_id IS NULL AND l_custom_setup_id = 118 THEN
1554          OPEN c_sd_request_header_id(l_utilization_rec.component_id);
1555          FETCH c_sd_request_header_id INTO l_utilization_rec.reference_id;
1556          CLOSE c_sd_request_header_id;
1557          l_utilization_rec.reference_type := 'SD_REQUEST';
1558 
1559          --kdass - bug 9470625 - populate Discount Amount, Discount Type, Discount Currency for SDR Offers
1560          OPEN c_sd_offer_discount(l_utilization_rec.price_adjustment_id);
1561          FETCH c_sd_offer_discount INTO l_utilization_rec.discount_amount, l_utilization_rec.discount_type;
1562          CLOSE c_sd_offer_discount;
1563 
1564          IF l_utilization_rec.discount_type in ('AMT', 'NEWPRICE') THEN
1565             l_utilization_rec.discount_amount_currency_code := l_utilization_rec.plan_currency_code;
1566          END IF;
1567       END IF;
1568 
1569       --feliu, add on 07/30/04 to populate adjustment if adjust_type_id is not null
1570       IF l_utilization_rec.adjustment_type_id IS NOT NULL THEN
1571            l_utilization_rec.utilization_type := 'ADJUSTMENT';
1572       END IF;
1573 
1574        --rimehrot for R12, if gl_posted_flag = Y or Null and gl_date is null, make gl_date = adjustment_date
1575       IF l_utilization_rec.gl_date IS NULL THEN
1576         IF l_utilization_rec.gl_posted_flag IS NULL OR l_utilization_rec.gl_posted_flag = G_GL_FLAG_YES THEN
1577           l_utilization_rec.gl_date := l_utilization_rec.adjustment_date;
1578         END IF;
1579       END IF;
1580 
1581       --get amount for universal currency and used to update rollup amount.
1582       IF g_universal_currency IS NULL THEN
1583          IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error) THEN
1584             fnd_message.set_name('OZF', 'OZF_UNIV_CURR_NOT_FOUND');
1585             fnd_msg_pub.add;
1586          END IF;
1587             RAISE fnd_api.g_exc_error;
1588       END IF;
1589 
1590       --rimehrot for R12, populate universal currency amount column
1591       IF g_universal_currency = l_utilization_rec.currency_code THEN
1592          l_utilization_rec.univ_curr_amount := l_utilization_rec.amount;
1593          l_utilization_rec.univ_curr_amount_remaining := l_utilization_rec.amount_remaining;
1594       ELSIF g_universal_currency = l_utilization_rec.plan_currency_code THEN
1595          l_utilization_rec.univ_curr_amount := l_utilization_rec.plan_curr_amount;
1596          l_utilization_rec.univ_curr_amount_remaining := l_utilization_rec.plan_curr_amount_remaining;
1597       ELSE
1598          /*Added for bug 7030415 - Send the exchange rate
1599         Utilization amount is converted from request curr to universal curr to populate univ_curr_amount
1600         column in ozf_funds_utilized_all_b */
1601 
1602         IF g_debug_flag = 'Y' THEN
1603          ozf_utility_pvt.write_conc_log('**************************START****************************');
1604          ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_utilization_rec.amount );
1605          ozf_utility_pvt.write_conc_log(l_api_name||' From Curr: '||l_utilization_rec.currency_code );
1606          ozf_utility_pvt.write_conc_log(l_api_name||' to curr univ_curr_amount: '|| g_universal_currency);
1607          ozf_utility_pvt.write_conc_log(l_api_name||' l_exchange_rate_type: '|| l_utilization_rec.exchange_rate_type);
1608         END IF;
1609          ozf_utility_pvt.convert_currency (
1610                    p_from_currency=> l_utilization_rec.plan_currency_code
1611                   ,p_to_currency=> g_universal_currency
1612                   ,p_conv_type=> l_utilization_rec.exchange_rate_type --Added for bug 7030415
1613                   ,p_from_amount=> l_utilization_rec.plan_curr_amount
1614                   ,x_return_status=> l_return_status
1615                   ,x_to_amount=> l_utilization_rec.univ_curr_amount
1616                   ,x_rate=> l_rate
1617                 );
1618          IF g_debug_flag = 'Y' THEN
1619           ozf_utility_pvt.write_conc_log(l_api_name||' Converted Amount l_utilization_rec.univ_curr_amount: '|| l_utilization_rec.univ_curr_amount);
1620           ozf_utility_pvt.write_conc_log('Utilization amount is converted from request curr to universal curr to populate univ_curr_amount column in izf_funds_utilized_all_b');
1621          END IF;
1622          IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1623             RAISE fnd_api.g_exc_unexpected_error;
1624          ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
1625             RAISE fnd_api.g_exc_error;
1626          END IF;
1627          /* Send the exchange rate for bug 7030415 */
1628          ozf_utility_pvt.convert_currency (
1629                    p_from_currency=> l_utilization_rec.plan_currency_code
1630                   ,p_to_currency=> g_universal_currency
1631                   ,p_conv_type=> l_utilization_rec.exchange_rate_type --Added for bug 7030415
1632                   ,p_from_amount=> l_utilization_rec.plan_curr_amount_remaining
1633                   ,x_return_status=> l_return_status
1634                   ,x_to_amount=> l_utilization_rec.univ_curr_amount_remaining
1635                   ,x_rate=> l_rate
1636                 );
1637          IF g_debug_flag = 'Y' THEN
1638            ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_utilization_rec.amount_remaining );
1639            ozf_utility_pvt.write_conc_log(l_api_name||' Converted Amount l_utilization_rec.univ_curr_amount_remaining: '|| l_utilization_rec.univ_curr_amount_remaining);
1640            ozf_utility_pvt.write_conc_log('Utilization amount is converted from request curr to universal curr to populate univ_curr_amount column in izf_funds_utilized_all_b');
1641            ozf_utility_pvt.write_conc_log('***************************END******************************');
1642          END IF;
1643          IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1644             RAISE fnd_api.g_exc_unexpected_error;
1645          ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
1646             RAISE fnd_api.g_exc_error;
1647          END IF;
1648       END IF; -- g_universal_currency = l_utilization_rec.currency_code
1649 
1650       --Fix for Bug 12657908
1651       OPEN c_get_year_id(l_utilization_rec.gl_date);
1652       FETCH c_get_year_id INTO l_utilization_rec.year_id;
1653       CLOSE c_get_year_id;
1654 
1655 
1656       IF g_debug_flag = 'Y' THEN
1657         ozf_utility_pvt.write_conc_log ('l_utilization_id ' || l_utilization_id);
1658         ozf_utility_pvt.write_conc_log ('l_obj_ver_num ' || l_obj_ver_num);
1659       END IF;
1660 
1661       IF l_utilization_id IS NULL THEN
1662       INSERT INTO ozf_funds_utilized_all_b
1663                      (utilization_id,last_update_date
1664                      ,last_updated_by,last_update_login
1665                      ,creation_date,created_by
1666                      ,created_from,request_id
1667                      ,program_application_id,program_id
1668                      ,program_update_date,utilization_type
1669                      ,fund_id,plan_type
1670                      ,plan_id,component_type,component_id
1671                      ,object_type,object_id
1672                      ,order_id,invoice_id
1673                      ,amount,acctd_amount
1674                      ,currency_code,exchange_rate_type
1675                      ,exchange_rate_date,exchange_rate
1676                      ,adjustment_type,adjustment_date
1677                      ,object_version_number,attribute_category
1678                      ,attribute1,attribute2
1679                      ,attribute3,attribute4
1680                      ,attribute5,attribute6
1681                      ,attribute7,attribute8
1682                      ,attribute9,attribute10
1683                      ,attribute11,attribute12
1684                      ,attribute13,attribute14
1685                      ,attribute15,org_id
1686                      ,adjustment_type_id,camp_schedule_id
1687                      ,gl_date, gl_posted_flag
1688                      ,product_level_type
1689                      ,product_id,ams_activity_budget_id
1690                      ,amount_remaining,acctd_amount_remaining
1691                      ,cust_account_id,price_adjustment_id
1692                      ,plan_curr_amount,plan_curr_amount_remaining
1693                      ,scan_unit,scan_unit_remaining
1694                      ,activity_product_id,volume_offer_tiers_id
1695                      --  11/04/2003   yzhao     11.5.10: added
1696                      ,billto_cust_account_id
1697                      ,reference_type
1698                      ,reference_id
1699                      /*fix for bug 4778995
1700                      ,month_id
1701                      ,quarter_id
1702                      ,year_id
1703                      */
1704                      ,order_line_id
1705                      ,orig_utilization_id -- added by feliu on 08/03/04
1706                      -- added by rimehrot for R12
1707                      ,bill_to_site_use_id
1708                      ,ship_to_site_use_id
1709                      ,univ_curr_amount
1710                      ,univ_curr_amount_remaining
1711                      ,fund_request_currency_code
1712                      ,fund_request_amount
1713                      ,fund_request_amount_remaining
1714                      ,plan_currency_code
1715                      --nirprasa, ER 10216374/9447673
1716                      ,cost_price
1717                      ,cost_price_currency_code
1718                      --kdass - bug 9470625
1719                      ,discount_type
1720                      ,discount_amount
1721                      ,discount_amount_currency_code
1722                      ,year_id -- Fix for Bug 12657908
1723         )
1724               VALUES (l_utilization_rec.utilization_id,SYSDATE -- LAST_UPDATE_DATE
1725                      ,NVL (fnd_global.user_id, -1),NVL (fnd_global.conc_login_id, -1) -- LAST_UPDATE_LOGIN
1726                      ,SYSDATE,NVL (fnd_global.user_id, -1) -- CREATED_BY
1727                      ,l_utilization_rec.created_from,fnd_global.conc_request_id -- REQUEST_ID
1728                      ,fnd_global.prog_appl_id,fnd_global.conc_program_id -- PROGRAM_ID
1729                      ,SYSDATE,l_utilization_rec.utilization_type
1730                      ,l_utilization_rec.fund_id,l_utilization_rec.plan_type
1731                      ,l_utilization_rec.plan_id,l_utilization_rec.component_type
1732                      ,l_utilization_rec.component_id,l_utilization_rec.object_type
1733                      ,l_utilization_rec.object_id,l_utilization_rec.order_id
1734                      ,l_utilization_rec.invoice_id,l_utilization_rec.amount
1735                      ,l_utilization_rec.acctd_amount,l_utilization_rec.currency_code
1736                      ,l_utilization_rec.exchange_rate_type,G_FAE_START_DATE
1737                      ,l_utilization_rec.exchange_rate,l_utilization_rec.adjustment_type
1738                      ,l_utilization_rec.adjustment_date,1 -- object_version_number
1739                      ,l_utilization_rec.attribute_category,l_utilization_rec.attribute1
1740                      ,l_utilization_rec.attribute2
1741                      ,l_utilization_rec.attribute3,l_utilization_rec.attribute4
1742                      ,l_utilization_rec.attribute5,l_utilization_rec.attribute6
1743                      ,l_utilization_rec.attribute7,l_utilization_rec.attribute8
1744                      ,l_utilization_rec.attribute9,l_utilization_rec.attribute10
1745                      ,l_utilization_rec.attribute11,l_utilization_rec.attribute12
1746                      ,l_utilization_rec.attribute13,l_utilization_rec.attribute14
1747                      ,l_utilization_rec.attribute15,l_utilization_rec.org_id--TO_NUMBER (SUBSTRB (USERENV ('CLIENT_INFO'), 1, 10)) -- org_id
1748                      ,l_utilization_rec.adjustment_type_id,l_utilization_rec.camp_schedule_id
1749                      ,l_utilization_rec.gl_date, l_utilization_rec.gl_posted_flag
1750                      ,l_utilization_rec.product_level_type
1751                      ,l_utilization_rec.product_id,l_utilization_rec.ams_activity_budget_id
1752                      ,l_utilization_rec.amount_remaining,l_utilization_rec.acctd_amount_remaining
1753                      ,l_utilization_rec.cust_account_id,l_utilization_rec.price_adjustment_id
1754                      ,l_utilization_rec.plan_curr_amount,l_utilization_rec.plan_curr_amount_remaining
1755                      ,l_utilization_rec.scan_unit,l_utilization_rec.scan_unit_remaining
1756                      ,l_utilization_rec.activity_product_id,l_utilization_rec.volume_offer_tiers_id
1757                      --  11/04/2003   yzhao     11.5.10: added
1758                      ,l_utilization_rec.billto_cust_account_id
1759                      ,l_utilization_rec.reference_type
1760                      ,l_utilization_rec.reference_id
1761                      /*fix for bug 4778995
1762                      ,l_utilization_rec.month_id
1763                      ,l_utilization_rec.quarter_id
1764                      ,l_utilization_rec.year_id
1765                      */
1766                      ,l_utilization_rec.order_line_id
1767                      ,l_utilization_rec.orig_utilization_id
1768                      -- added by rimehrot for R12
1769                     ,l_utilization_rec.bill_to_site_use_id
1770                     ,l_utilization_rec.ship_to_site_use_id
1771                     ,l_utilization_rec.univ_curr_amount
1772                     ,l_utilization_rec.univ_curr_amount_remaining
1773                     ,l_utilization_rec.fund_request_currency_code
1774                     ,l_utilization_rec.fund_request_amount
1775                     ,l_utilization_rec.fund_request_amount_remaining
1776                     ,l_utilization_rec.plan_currency_code
1777                     --nirprasa, ER 10216374/9447673
1778                     ,l_utilization_rec.cost_price
1779                     ,l_utilization_rec.cost_price_currency_code
1780                     --kdass - bug 9470625
1781                     ,l_utilization_rec.discount_type
1782                     ,l_utilization_rec.discount_amount
1783                     ,l_utilization_rec.discount_amount_currency_code
1784                     ,l_utilization_rec.year_id -- Fix for Bug 12657908
1785 
1786              );
1787 
1788          INSERT INTO ozf_funds_utilized_all_tl
1789                      (utilization_id,last_update_date
1790                      ,last_updated_by,last_update_login
1791                      ,creation_date,created_by
1792                      ,created_from,request_id
1793                      ,program_application_id,program_id
1794                      ,program_update_date,adjustment_desc
1795                      ,source_lang,language
1796                      ,org_id
1797                      )
1798             SELECT l_utilization_rec.utilization_id
1799                   ,SYSDATE -- LAST_UPDATE_DATE
1800                   ,NVL (fnd_global.user_id, -1) -- LAST_UPDATED_BY
1801                   ,NVL (fnd_global.conc_login_id, -1) -- LAST_UPDATE_LOGIN
1802                   ,SYSDATE -- CREATION_DATE
1803                   ,NVL (fnd_global.user_id, -1) -- CREATED_BY
1804                   ,l_utilization_rec.created_from -- CREATED_FROM
1805                   ,fnd_global.conc_request_id -- REQUEST_ID
1806                   ,fnd_global.prog_appl_id -- PROGRAM_APPLICATION_ID
1807                   ,fnd_global.conc_program_id -- PROGRAM_ID
1808                   ,SYSDATE -- PROGRAM_UPDATE_DATE
1809                   ,l_utilization_rec.adjustment_desc -- ADJUSTMENT_DESCRIPTION
1810                   ,USERENV ('LANG') -- SOURCE_LANGUAGE
1811                   ,l.language_code -- LANGUAGE
1812                   ,l_utilization_rec.org_id --TO_NUMBER (SUBSTRB (USERENV ('CLIENT_INFO'), 1, 10)) -- org_id
1813               FROM fnd_languages l
1814               WHERE l.installed_flag IN ('I', 'B')
1815               AND NOT EXISTS ( SELECT NULL
1816                                   FROM ozf_funds_utilized_all_tl t
1817                                  WHERE t.utilization_id = l_utilization_rec.utilization_id
1818                                    AND t.language = l.language_code);
1819 
1820          x_utilization_id :=       l_utilization_rec.utilization_id  ;
1821          ELSE
1822          --UPDATE UTILIZATION TABLE
1823          --Bug 13463758 Decide if it is partial shipment/backorder/split
1824          --scenario and skip to update instead of insert.
1825          UPDATE ozf_funds_utilized_all_b
1826              SET amount = amount+l_utilization_rec.amount, amount_remaining = amount_remaining+l_utilization_rec.amount_remaining,
1827                  plan_curr_amount = plan_curr_amount+l_utilization_rec.plan_curr_amount,
1828                  plan_curr_amount_remaining = plan_curr_amount_remaining+l_utilization_rec.plan_curr_amount_remaining,
1829                  acctd_amount = acctd_amount+l_utilization_rec.acctd_amount,
1830                  acctd_amount_remaining = acctd_amount_remaining+l_utilization_rec.acctd_amount_remaining,
1831                  fund_request_amount = fund_request_amount+l_utilization_rec.fund_request_amount,
1832                  fund_request_amount_remaining = fund_request_amount_remaining+l_utilization_rec.fund_request_amount_remaining,
1833                  univ_curr_amount = univ_curr_amount+l_utilization_rec.univ_curr_amount,
1834                  univ_curr_amount_remaining = univ_curr_amount_remaining+l_utilization_rec.univ_curr_amount_remaining,
1835                  exchange_rate_type = l_utilization_rec.exchange_rate_type, exchange_rate_date = G_FAE_START_DATE,
1836                  exchange_rate = l_utilization_rec.exchange_rate, last_update_date = SYSDATE,
1837                  last_updated_by = NVL (fnd_global.user_id, -1), last_update_login = NVL (fnd_global.conc_login_id, -1),
1838                  object_version_number = l_obj_ver_num + 1
1839              WHERE utilization_id = l_utilization_id
1840              AND object_version_number = l_obj_ver_num;
1841 
1842          UPDATE ozf_funds_utilized_all_tl
1843              SET last_update_date = SYSDATE, last_updated_by = NVL (fnd_global.user_id, -1), last_update_login = NVL (fnd_global.conc_login_id, -1),
1844                 creation_date = SYSDATE, created_by = NVL (fnd_global.user_id, -1), request_id = fnd_global.conc_request_id,
1845                 program_application_id = fnd_global.prog_appl_id, program_id = fnd_global.conc_program_id, program_update_date = SYSDATE,
1846                 org_id = l_utilization_rec.org_id
1847              WHERE utilization_id = l_utilization_id;
1848          x_utilization_id := l_utilization_id  ;
1849          END IF;
1850 
1851          l_utilization_id := NULL;
1852          l_obj_ver_num := NULL;
1853 
1854 
1855          IF l_utilization_rec.utilization_type IN ('ACCRUAL', 'SALES_ACCRUAL', 'UTILIZED', 'ADJUSTMENT') THEN
1856             /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
1857                 OPEN c_mc_trans (l_utilization_rec.fund_id);
1858                 FETCH c_mc_trans INTO l_mc_record_id
1859                                      ,l_mc_obj_num
1860                                      ,l_mc_col_1
1861                                      ,l_mc_col_6        -- yzhao: 10/14/2003 added
1862                                      ,l_mc_col_7
1863                                      ,l_mc_col_8
1864                      ,l_mc_col_9;
1865                 IF (c_mc_trans%NOTFOUND) THEN
1866                    CLOSE c_mc_trans;
1867                    IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1868                       fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1869                       fnd_msg_pub.ADD;
1870                    END IF;
1871                    RAISE fnd_api.g_exc_error;
1872                 END IF;
1873                 CLOSE c_mc_trans;
1874             */
1875                -- rimehrot changed for R12, Populate new table ozf_object_fund_summary
1876                -- rimehrot: component_id/type is the destination. Will always be equal to plan_id/type in this case
1877             l_objfundsum_rec := NULL;
1878             OPEN c_get_objfundsum_rec(l_utilization_rec.component_type
1879                                      , l_utilization_rec.component_id
1880                                      , l_utilization_rec.fund_id);
1881             FETCH c_get_objfundsum_rec INTO l_objfundsum_rec.objfundsum_id
1882                                            , l_objfundsum_rec.object_version_number
1883                                            , l_objfundsum_rec.committed_amt
1884                                            , l_objfundsum_rec.recal_committed_amt
1885                                            , l_objfundsum_rec.utilized_amt
1886                                            , l_objfundsum_rec.earned_amt
1887                                            , l_objfundsum_rec.paid_amt
1888                                            , l_objfundsum_rec.plan_curr_committed_amt
1889                                            , l_objfundsum_rec.plan_curr_recal_committed_amt
1890                                            , l_objfundsum_rec.plan_curr_utilized_amt
1891                                            , l_objfundsum_rec.plan_curr_earned_amt
1892                                            , l_objfundsum_rec.plan_curr_paid_amt
1893                                            , l_objfundsum_rec.univ_curr_committed_amt
1894                                            , l_objfundsum_rec.univ_curr_recal_committed_amt
1895                                            , l_objfundsum_rec.univ_curr_utilized_amt
1896                                            , l_objfundsum_rec.univ_curr_earned_amt
1897                                            , l_objfundsum_rec.univ_curr_paid_amt;
1898             CLOSE c_get_objfundsum_rec;
1899 
1900             IF l_fund_type = 'FULLY_ACCRUED' THEN
1901                -- for a fully accrued customer fund with liability flag on, the budgeted, utilized and committed column gets populated
1902                -- 11.5.10: update utilized_amt, not earned_amt
1903                IF l_accrual_basis = 'CUSTOMER' AND NVL(l_liability_flag, 'N') = 'Y' THEN
1904                   l_original_budget := NVL (l_original_budget, 0)+ NVL (l_utilization_rec.amount, 0);
1905                   l_utilized_amt     := NVL (l_utilized_amt, 0)+ NVL (l_utilization_rec.amount, 0);
1906                   l_rollup_orig_amt :=NVL(l_rollup_orig_amt,0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1907                   l_rollup_utilized_amt := NVL(l_rollup_utilized_amt,0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1908                   -- l_mc_col_1     := NVL(l_mc_col_1,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1909                   -- l_mc_col_9     := NVL(l_mc_col_9,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1910                   l_new_orig_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1911                   l_new_utilized_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1912                   l_new_paid_amt := 0;
1913 
1914                  -- rimehrot changed for R12, Populate utilized/committed/recal_committed in ozf_object_fund_summary
1915                   l_objfundsum_rec.utilized_amt := NVL(l_objfundsum_rec.utilized_amt, 0) + NVL(l_utilization_rec.amount, 0);
1916                   l_objfundsum_rec.plan_curr_utilized_amt := NVL(l_objfundsum_rec.plan_curr_utilized_amt, 0)
1917                                                                --nirprasa,use new plan currency column
1918                                                                -- + NVL(l_utilization_rec.plan_curr_amount, 0);*/
1919                                                                + NVL(l_utilization_rec.fund_request_amount, 0);
1920                   l_objfundsum_rec.univ_curr_utilized_amt := NVL(l_objfundsum_rec.univ_curr_utilized_amt, 0)
1921                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1922                   l_objfundsum_rec.committed_amt := NVL(l_objfundsum_rec.committed_amt, 0) + NVL(l_utilization_rec.amount, 0);
1923                   l_objfundsum_rec.plan_curr_committed_amt := NVL(l_objfundsum_rec.plan_curr_committed_amt, 0)
1924                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1925                   l_objfundsum_rec.univ_curr_committed_amt := NVL(l_objfundsum_rec.univ_curr_committed_amt, 0)
1926                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1927                   l_objfundsum_rec.recal_committed_amt := NVL(l_objfundsum_rec.recal_committed_amt, 0)
1928                                                                   + NVL(l_utilization_rec.amount, 0);
1929                   l_objfundsum_rec.plan_curr_recal_committed_amt := NVL(l_objfundsum_rec.plan_curr_recal_committed_amt, 0)
1930                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1931                   l_objfundsum_rec.univ_curr_recal_committed_amt := NVL(l_objfundsum_rec.univ_curr_recal_committed_amt, 0)
1932                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1933                  -- rimehrot: end changes for R12
1934 
1935                   -- yzhao: 10/14/2003 Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
1936                   -- l_mc_col_6     := NVL(l_mc_col_6,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1937                   l_new_committed_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1938                   l_new_recal_committed := NVL (l_utilization_rec.univ_curr_amount, 0);
1939                   l_committed_amt := NVL(l_committed_amt, 0) + NVL (l_utilization_rec.amount, 0);
1940                   l_rollup_committed_amt := NVL(l_rollup_committed_amt, 0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1941                   l_recal_committed := NVL(l_recal_committed, 0) + NVL (l_utilization_rec.amount, 0);
1942                   l_rollup_recal_committed := NVL(l_rollup_recal_committed, 0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1943 
1944                   -- 10/14/2003  update ozf_act_budgets REQUEST between fully accrual budget and its offer when accrual happens
1945                   OPEN  c_accrual_budget_reqeust(l_utilization_rec.fund_id, l_plan_id);
1946                   FETCH c_accrual_budget_reqeust INTO l_act_budget_id, l_act_budget_objver;
1947                   IF (c_accrual_budget_reqeust%NOTFOUND) THEN
1948                      ozf_utility_pvt.write_conc_log ('    D: create_utilized_rec() ERROR customer fully accrual budget. can not find approved budget request record between fund '
1949                                      || l_utilization_rec.fund_id || ' and offer ' || l_plan_id);
1950                      CLOSE c_accrual_budget_reqeust;
1951                      IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1952                        fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1953                        fnd_msg_pub.ADD;
1954                      END IF;
1955                      RAISE fnd_api.g_exc_error;
1956                   END IF;
1957                   CLOSE c_accrual_budget_reqeust;
1958 
1959                   UPDATE ozf_act_budgets
1960                     SET    request_amount = NVL(request_amount, 0) + l_utilization_rec.plan_curr_amount
1961                           , src_curr_request_amt = NVL(src_curr_request_amt, 0) + l_utilization_rec.amount
1962                           , approved_amount = NVL(approved_amount, 0) + l_utilization_rec.fund_request_amount
1963                           , approved_original_amount = NVL(approved_original_amount, 0) + l_utilization_rec.amount
1964                           , approved_amount_fc = NVL(approved_amount_fc, 0) + l_utilization_rec.acctd_amount
1965                           , last_update_date = sysdate
1966                           , last_updated_by = NVL (fnd_global.user_id, -1)
1967                           , last_update_login = NVL (fnd_global.conc_login_id, -1)
1968                           , object_version_number = l_act_budget_objver + 1
1969                   WHERE  activity_budget_id = l_act_budget_id
1970                   AND    object_version_number = l_act_budget_objver;
1971 
1972               -- 4619156, comment as request no longer in util table.
1973                /*   OPEN c_budget_request_utilrec(l_utilization_rec.fund_id, l_plan_id, l_act_budget_id);
1974                   FETCH c_budget_request_utilrec INTO l_act_budget_id, l_act_budget_objver;
1975                   IF (c_budget_request_utilrec%NOTFOUND) THEN
1976                       write_conc_log ('    D: create_utilized_rec() ERROR customer fully accrual budget. can not find approved budget request record in utilization table between fund '
1977                                       || l_utilization_rec.fund_id || ' and offer ' || l_plan_id);
1978                       CLOSE c_budget_request_utilrec;
1979                       IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1980                          fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1981                          fnd_msg_pub.ADD;
1982                       END IF;
1983                       RAISE fnd_api.g_exc_error;
1984                   END IF;
1985                   CLOSE c_budget_request_utilrec;
1986 
1987                   -- populate request amount in ozf_funds_utilized_all_b record
1988                   UPDATE ozf_funds_utilized_all_b
1989                   SET    amount = NVL(amount,0) + NVL(l_utilization_rec.amount,0)
1990                        , plan_curr_amount = NVL(plan_curr_amount,0) + NVL(l_utilization_rec.plan_curr_amount,0)
1991                        , univ_curr_amount = NVL(univ_curr_amount, 0) + NVL(l_utilization_rec.univ_curr_amount, 0)
1992                        , acctd_amount = NVL(acctd_amount,0) + NVL(l_utilization_rec.acctd_amount,0)
1993                        , last_update_date = sysdate
1994                        , last_updated_by = NVL (fnd_global.user_id, -1)
1995                        , last_update_login = NVL (fnd_global.conc_login_id, -1)
1996                        , object_version_number = l_act_budget_objver + 1
1997                   WHERE  utilization_id = l_act_budget_id
1998                   AND    object_version_number = l_act_budget_objver;*/
1999                   -- yzhao: 10/14/2003 END Fix TEVA bug - customer fully accrual budget committed amount is always 0
2000 
2001                -- for a fully accrued sales fund and customer accrual with liability flag off,
2002                -- then only the budgeted column gets populated
2003                -- ELSIF l_accrual_basis = 'SALES' THEN
2004             /*  feliu1122
2005                ELSE
2006                   l_original_budget :=NVL (l_original_budget, 0)+ NVL (l_utilization_rec.amount, 0);
2007                   l_rollup_orig_amt :=NVL(l_rollup_orig_amt,0) + NVL (l_new_univ_amt, 0);
2008                   -- l_mc_col_1     := NVL(l_mc_col_1,0) +  NVL (l_utilization_rec.acctd_amount, 0);
2009                   l_new_orig_amt := NVL (l_new_univ_amt, 0);
2010                   l_new_utilized_amt := 0;
2011                   l_new_paid_amt := 0;
2012 */             END IF;
2013             ELSE -- for fixed budget
2014                   -- utilized is always updated for Accrual or Utilized record
2015                l_utilized_amt      := NVL (l_utilized_amt, 0) + NVL (l_utilization_rec.amount, 0);
2016                l_rollup_utilized_amt := NVL(l_rollup_utilized_amt,0) + NVL (l_utilization_rec.univ_curr_amount, 0);
2017                l_new_utilized_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
2018                   -- l_mc_col_9     := NVL(l_mc_col_9,0) +  NVL (l_utilization_rec.acctd_amount, 0);
2019                   -- rimehrot: for R12, populate utilized amount
2020                l_objfundsum_rec.utilized_amt := NVL(l_objfundsum_rec.utilized_amt, 0) + NVL(l_utilization_rec.amount, 0);
2021                l_objfundsum_rec.plan_curr_utilized_amt := NVL(l_objfundsum_rec.plan_curr_utilized_amt, 0)
2022                                                                 --  + NVL(l_utilization_rec.plan_curr_amount, 0);
2023                                                                 + NVL(l_utilization_rec.fund_request_amount, 0);
2024                l_objfundsum_rec.univ_curr_utilized_amt := NVL(l_objfundsum_rec.univ_curr_utilized_amt, 0)
2025                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
2026 
2027                   -- end R12 changes
2028                   -- 11.5.10: for off-invoice offer, if posting to gl flag is off, utilized, eanred and paid updated the same time
2029                   --          if flag is on, only utilized will be updated, earned and paid will be updated after gl posting
2030                   --          fix bug 3428988 - for accrual offer, do not update paid and earned amount when creating utilization
2031                   /* feliu 1121
2032                   IF l_utilization_rec.utilization_type = 'UTILIZED' AND l_off_invoice_gl_post_flag = 'F' THEN
2033                      l_earned_amt      := NVL (l_earned_amt, 0) + NVL (l_utilization_rec.amount, 0);
2034                      l_rollup_earned_amt := NVL(l_rollup_earned_amt,0) + NVL (l_new_univ_amt, 0);
2035                      l_new_earned_amt := NVL (l_new_univ_amt, 0);
2036                      -- l_mc_col_7     := NVL(l_mc_col_7,0) +  NVL (l_utilization_rec.acctd_amount, 0);
2037                      l_paid_amt      := NVL (l_paid_amt, 0) + NVL (l_utilization_rec.amount, 0);
2038                      l_rollup_paid_amt := NVL(l_rollup_paid_amt,0) + NVL (l_new_univ_amt, 0);
2039                      l_new_paid_amt := NVL (l_new_univ_amt, 0);
2040                      -- l_mc_col_8     := NVL(l_mc_col_8,0) +  NVL (l_utilization_rec.acctd_amount, 0);
2041                      -- rimehrot: for R12, populate earned/paid amount
2042                      l_objfundsum_rec.earned_amt := NVL(l_objfundsum_rec.earned_amt, 0) + NVL(l_utilization_rec.amount, 0);
2043                      l_objfundsum_rec.plan_curr_earned_amt := NVL(l_objfundsum_rec.plan_curr_earned_amt, 0)
2044                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
2045                      l_objfundsum_rec.univ_curr_earned_amt := NVL(l_objfundsum_rec.univ_curr_earned_amt, 0)
2046                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
2047 
2048                      l_objfundsum_rec.paid_amt := NVL(l_objfundsum_rec.paid_amt, 0) + NVL(l_utilization_rec.amount, 0);
2049                      l_objfundsum_rec.plan_curr_paid_amt := NVL(l_objfundsum_rec.plan_curr_paid_amt, 0)
2050                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
2051                      l_objfundsum_rec.univ_curr_paid_amt := NVL(l_objfundsum_rec.univ_curr_paid_amt, 0)
2052                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
2053                      -- end R12 changes
2054                   END IF;  */
2055             END IF; -- end of fund_type.
2056 
2057             UPDATE ozf_funds_all_b
2058             SET original_budget =  l_original_budget,
2059                 utilized_amt = l_utilized_amt,
2060                 earned_amt = l_earned_amt,
2061                 paid_amt = l_paid_amt,
2062                 object_version_number = l_obj_num + 1
2063                 ,rollup_original_budget = l_rollup_orig_amt
2064                 ,rollup_utilized_amt = l_rollup_utilized_amt
2065                 ,rollup_earned_amt = l_rollup_earned_amt
2066                 ,rollup_paid_amt = l_rollup_paid_amt
2067                 -- yzhao: 10/14/2003 Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
2068                 ,committed_amt = l_committed_amt
2069                 ,rollup_committed_amt = l_rollup_committed_amt
2070                 ,recal_committed = l_recal_committed
2071                 ,rollup_recal_committed = l_rollup_recal_committed
2072             WHERE fund_id =  l_utilization_rec.fund_id
2073             AND object_version_number = l_obj_num;
2074 
2075             IF l_parent_fund_id is NOT NULL THEN
2076                FOR fund IN c_parent(l_parent_fund_id)
2077                LOOP
2078                   UPDATE ozf_funds_all_b
2079                   SET object_version_number = fund.object_version_number + 1
2080                    ,rollup_original_budget = NVL(fund.rollup_original_budget,0) + NVL(l_new_orig_amt,0)
2081                    ,rollup_earned_amt = NVL(fund.rollup_earned_amt,0) + NVL(l_new_earned_amt,0)
2082                    ,rollup_paid_amt = NVL(fund.rollup_paid_amt,0) + NVL(l_new_paid_amt,0)
2083                    -- yzhao: 10/14/2003 Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
2084                    ,rollup_committed_amt = NVL(fund.rollup_committed_amt, 0) + NVL(l_new_committed_amt, 0)
2085                    ,rollup_recal_committed = NVL(fund.rollup_recal_committed, 0) + NVL(l_new_recal_committed, 0)
2086                    -- yzhao: 11.5.10
2087                    ,rollup_utilized_amt = NVL(fund.rollup_utilized_amt,0) + NVL(l_new_utilized_amt,0)
2088                   WHERE fund_id = fund.fund_id
2089                   AND object_version_number = fund.object_version_number;
2090                 END LOOP;
2091             END IF;
2092 
2093           -- rimehrot: for R12, create or update in ozf_object_fund_summary
2094             IF l_objfundsum_rec.objfundsum_id IS NULL THEN
2095                l_objfundsum_rec.fund_id := l_utilization_rec.fund_id;
2096                l_objfundsum_rec.fund_currency := l_utilization_rec.currency_code;
2097                l_objfundsum_rec.object_type := l_utilization_rec.component_type;
2098                l_objfundsum_rec.object_id := l_utilization_rec.component_id;
2099                ozf_objfundsum_pvt.create_objfundsum(
2100                        p_api_version                => 1.0,
2101                        p_init_msg_list              => Fnd_Api.G_FALSE,
2102                        p_validation_level           => Fnd_Api.G_VALID_LEVEL_NONE,
2103                        p_objfundsum_rec             => l_objfundsum_rec,
2104                        x_return_status              => l_return_status,
2105                        x_msg_count                  => x_msg_count,
2106                        x_msg_data                   => x_msg_data,
2107                        x_objfundsum_id              => l_objfundsum_id
2108                 );
2109                IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
2110                   RAISE fnd_api.g_exc_unexpected_error;
2111                ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
2112                   RAISE fnd_api.g_exc_error;
2113                END IF;
2114             ELSE
2115                ozf_objfundsum_pvt.update_objfundsum(
2116                        p_api_version                => 1.0,
2117                        p_init_msg_list              => Fnd_Api.G_FALSE,
2118                        p_validation_level           => Fnd_Api.G_VALID_LEVEL_NONE,
2119                        p_objfundsum_rec             => l_objfundsum_rec,
2120                        x_return_status              => l_return_status,
2121                        x_msg_count                  => x_msg_count,
2122                        x_msg_data                   => x_msg_data
2123                 );
2124                IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
2125                   RAISE fnd_api.g_exc_unexpected_error;
2126                ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
2127                   RAISE fnd_api.g_exc_error;
2128                END IF;
2129             END IF;
2130             -- rimehrot: end changes for R12
2131 
2132           /* R12 yzhao: bug 4669269 - obsolete ozf_mc_transactions
2133           -- update ozf_mc_transaction_all table.
2134           UPDATE ozf_mc_transactions_all
2135             SET amount_column1 =l_mc_col_1,
2136                 amount_column6 =l_mc_col_6,   -- yzhao: 10/14/2003
2137                 amount_column7 =l_mc_col_7,
2138                 amount_column8 =l_mc_col_8,
2139                 amount_column9 =l_mc_col_9,   -- yzhao: 11.5.10 for utilized_amt
2140                 object_version_number = l_mc_obj_num + 1
2141             WHERE mc_record_id = l_mc_record_id
2142             AND object_version_number = l_mc_obj_num;
2143            */
2144          END IF; -- end if utilization type
2145 
2146         /* yzhao: 03/19/2003 post to GL when order is shipped. move to function post_accrual_to_gl */
2147 
2148         IF g_debug_flag = 'Y' THEN
2149          ozf_utility_pvt.write_conc_log(   l_full_name
2150                                      || ': end' || l_event_id);
2151         END IF;
2152 
2153         fnd_msg_pub.count_and_get (
2154             p_count=> x_msg_count,
2155             p_data=> x_msg_data,
2156             p_encoded=> fnd_api.g_false
2157          );
2158 
2159    EXCEPTION
2160       WHEN fnd_api.g_exc_error THEN
2161          ROLLBACK TO create_utilized_rec;
2162          x_return_status            := fnd_api.g_ret_sts_error;
2163          fnd_msg_pub.count_and_get (
2164             p_count=> x_msg_count,
2165             p_data=> x_msg_data,
2166             p_encoded=> fnd_api.g_false
2167          );
2168 
2169       WHEN fnd_api.g_exc_unexpected_error THEN
2170          ROLLBACK TO create_utilized_rec;
2171          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2172          fnd_msg_pub.count_and_get (
2173             p_count=> x_msg_count,
2174             p_data=> x_msg_data,
2175             p_encoded=> fnd_api.g_false
2176          );
2177 
2178       WHEN OTHERS THEN
2179          ROLLBACK TO create_utilized_rec;
2180          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2181          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2182             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
2183          END IF;
2184          fnd_msg_pub.count_and_get (
2185             p_count=> x_msg_count,
2186             p_data=> x_msg_data,
2187             p_encoded=> fnd_api.g_false
2188          );
2189 
2190 
2191    END create_utilized_rec;
2192 
2193 ----------------------------------------------------------------------------------
2194 -- Procedure Name
2195 --  create_utilization
2196 -- created by mpande 02/08/2002
2197 -- Purpose
2198 --   This procedure will create utiliation records for the order accruals
2199 -----------------------------------------------------------------------------------
2200    PROCEDURE create_fund_utilization (
2201       p_act_util_rec      IN       ozf_fund_utilized_pvt.utilization_rec_type,
2202       p_act_budgets_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type,
2203       x_utilization_id    OUT NOCOPY      NUMBER,
2204       x_return_status     OUT NOCOPY      VARCHAR2,
2205       x_msg_count         OUT NOCOPY      NUMBER,
2206       x_msg_data          OUT NOCOPY      VARCHAR2
2207    ) IS
2208       l_api_version           NUMBER                                  := 1.0;
2209       l_api_name              VARCHAR2 (60)                           := 'create_fund_utilization';
2210       l_act_budget_id         NUMBER;
2211       l_act_budgets_rec       ozf_actbudgets_pvt.act_budgets_rec_type := p_act_budgets_rec;
2212       l_act_util_rec          ozf_fund_utilized_pvt.utilization_rec_type    := p_act_util_rec;
2213       l_activity_id           NUMBER;
2214       l_obj_ver_num           NUMBER;
2215       l_old_approved_amount   NUMBER;
2216       l_old_parent_src_amt    NUMBER;
2217       l_ledger_id             NUMBER;
2218       l_ledger_name           VARCHAR2(30);
2219       l_utilization_id        NUMBER;
2220 
2221       /* -- 6/3/2002 mpande changed as per PM specifications --
2222         We should accrue to the bill to org but not o the sold to org
2223       CURSOR c_cust_number (p_header_id IN NUMBER) IS
2224          SELECT sold_to_org_id
2225            FROM oe_order_headers_all
2226           WHERE header_id = p_header_id;
2227          */
2228       CURSOR c_cust_number (p_header_id IN NUMBER) IS
2229          SELECT cust.cust_account_id, header.invoice_to_org_id, header.ship_to_org_id
2230            FROM hz_cust_acct_sites_all acct_site,
2231                 hz_cust_site_uses_all site_use,
2232                 hz_cust_accounts  cust,
2233                 oe_order_headers_all header
2234           WHERE header.header_id = p_header_id
2235               AND acct_site.cust_acct_site_id = site_use.cust_acct_site_id
2236             AND acct_site.cust_account_id = cust.cust_account_id
2237             AND site_use.site_use_id = header.invoice_to_org_id ;
2238 
2239       -- Cursor to get the org_id for order
2240       CURSOR c_org_id (p_order_header_id IN NUMBER)IS
2241          SELECT org_id FROM oe_order_headers_all
2242          WHERE header_id = p_order_header_id;
2243 
2244       --nirprasa,ER 8399134
2245       CURSOR c_offer_info (p_list_header_id IN NUMBER) IS
2246          SELECT qp.orig_org_id offer_org_id
2247         FROM qp_list_headers_all qp, ozf_offers off
2248           WHERE qp.list_header_id = p_list_header_id
2249             AND qp.list_header_id = off.qp_list_header_id;
2250 
2251       l_offer_info            c_offer_info%ROWTYPE;
2252    BEGIN
2253       SAVEPOINT create_fund_utilization_acr;
2254       x_return_status            := fnd_api.g_ret_sts_success;
2255       IF g_debug_flag = 'Y' THEN
2256          ozf_utility_pvt.write_conc_log ('    D:  Enter create_fund_utilization() ');
2257       END IF;
2258       l_act_util_rec.product_level_type := 'PRODUCT';
2259       IF l_act_util_rec.billto_cust_account_id IS NULL THEN
2260           --  customer id
2261           OPEN c_cust_number (p_act_util_rec.object_id);
2262           FETCH c_cust_number INTO l_act_util_rec.billto_cust_account_id, l_act_util_rec.bill_to_site_use_id, l_act_util_rec.ship_to_site_use_id;
2263           CLOSE c_cust_number;
2264       END IF;
2265 
2266       l_act_budgets_rec.justification := fnd_message.get_string ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK');
2267       l_act_budgets_rec.transfer_type := 'UTILIZED';
2268       l_act_budgets_rec.request_date := SYSDATE;
2269       l_act_budgets_rec.status_code := 'APPROVED';
2270       l_act_budgets_rec.user_status_id :=
2271             ozf_utility_pvt.get_default_user_status (
2272                'OZF_BUDGETSOURCE_STATUS',
2273                l_act_budgets_rec.status_code
2274             );
2275       --nirprasa, ER 8399134 Arrow's case: If offer is not a global offer and applied to an order
2276       -- of different OU then use offer's org.
2277       OPEN c_offer_info(l_act_util_rec.plan_id);
2278       FETCH c_offer_info INTO l_offer_info;
2279       CLOSE c_offer_info;
2280 
2281       IF l_offer_info.offer_org_id IS NOT NULL AND l_offer_info.offer_org_id  <> l_act_util_rec.org_id THEN
2282          l_act_util_rec.org_id := l_offer_info.offer_org_id ;
2283       END IF;
2284       --end ER 8399134
2285       IF l_act_util_rec.org_id IS NULL THEN
2286           OPEN c_org_id( l_act_util_rec.object_id) ;
2287           FETCH c_org_id INTO l_act_util_rec.org_id;
2288           CLOSE c_org_id ;
2289       END IF;
2290 
2291       IF g_debug_flag = 'Y' THEN
2292       ozf_utility_pvt.write_conc_log ('  l_act_budgets_rec.user_status_id '||l_act_budgets_rec.user_status_id);
2293       ozf_utility_pvt.write_conc_log ('  l_act_budgets_rec.org_id '||l_act_util_rec.org_id);
2294       END IF;
2295 
2296       --get the order's ledger id
2297       mo_utils.Get_Ledger_Info (p_operating_unit => l_act_util_rec.org_id
2298                                ,p_ledger_id      => l_ledger_id
2299                                ,p_ledger_name    => l_ledger_name);
2300       IF g_debug_flag = 'Y' THEN
2301       ozf_utility_pvt.write_conc_log (' l_ledger_id '||l_ledger_id);
2302       ozf_utility_pvt.write_conc_log (' l_ledger_name '|| l_ledger_name);
2303       END IF;
2304 
2305       create_actbudgets_rec (
2306         x_return_status       =>x_return_status
2307         ,x_msg_count          =>x_msg_count
2308         ,x_msg_data           =>x_msg_data
2309         ,x_act_budget_id      =>l_activity_id
2310         ,p_act_budgets_rec    =>l_act_budgets_rec
2311         ,p_ledger_id          => l_ledger_id        -- yzhao: added for R12
2312         ,p_org_id             =>l_act_util_rec.org_id -- nirprasa added to get conversion type for bug 7030415
2313       );
2314 
2315       IF x_return_status <> fnd_api.g_ret_sts_success THEN
2316          ozf_utility_pvt.write_conc_log (': create Act Budgets Failed '||x_return_status);
2317          IF x_return_status = fnd_api.g_ret_sts_error THEN
2318             RAISE fnd_api.g_exc_error;
2319          ELSIF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
2320             RAISE fnd_api.g_exc_unexpected_error;
2321          END IF;
2322       END IF;
2323 
2324       l_act_util_rec.ams_activity_budget_id := l_activity_id;
2325       create_utilized_rec (
2326         x_return_status      =>x_return_status
2327         ,x_msg_count           =>x_msg_count
2328         ,x_msg_data           =>x_msg_data
2329         ,x_utilization_id     =>l_utilization_id
2330         ,p_utilization_rec    =>l_act_util_rec
2331       );
2332 
2333       x_utilization_id := l_utilization_id;
2334 
2335       IF x_return_status <>fnd_api.g_ret_sts_success THEN
2336          ozf_utility_pvt.write_conc_log (': create utilization Failed '||x_return_status);
2337          IF x_return_status = fnd_api.g_ret_sts_error THEN
2338             RAISE fnd_api.g_exc_error;
2339          ELSIF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
2340             RAISE fnd_api.g_exc_unexpected_error;
2341          END IF;
2342       END IF;
2343 
2344       fnd_msg_pub.count_and_get (
2345          p_count=> x_msg_count,
2346          p_data=>x_msg_data,
2347          p_encoded=> fnd_api.g_false
2348       );
2349    EXCEPTION
2350       WHEN fnd_api.g_exc_error THEN
2351          ROLLBACK TO create_fund_utilization_acr;
2352          x_return_status            := fnd_api.g_ret_sts_error;
2353          fnd_msg_pub.count_and_get (
2354             p_count=> x_msg_count
2355            ,p_data=> x_msg_data
2356            ,p_encoded=> fnd_api.g_false
2357          );
2358       WHEN fnd_api.g_exc_unexpected_error THEN
2359          ROLLBACK TO create_fund_utilization_acr;
2360          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2361          fnd_msg_pub.count_and_get (
2362             p_count=> x_msg_count
2363            ,p_data=> x_msg_data
2364            ,p_encoded=> fnd_api.g_false
2365          );
2366       WHEN OTHERS THEN
2367          ROLLBACK TO create_fund_utilization_acr;
2368          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2369 
2370          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2371             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
2372          END IF;
2373 
2374          fnd_msg_pub.count_and_get (
2375             p_count=> x_msg_count
2376            ,p_data=> x_msg_data
2377            ,p_encoded=> fnd_api.g_false
2378          );
2379    END create_fund_utilization;
2380 
2381 /*----------------------------------------------------------------------------
2382 -- Procedure Name
2383 --   post_accrual_to_budget
2384 -- Purpose
2385 --   This procedure will post accrual to budget proportionally, and create utilization records
2386 --   extracted from adjust_accrual so it can be reused
2387 --
2388 -- Parameters:
2389 --
2390 -- History
2391 --  created      yzhao     03/21/03
2392 ------------------------------------------------------------------------------*/
2393    PROCEDURE post_accrual_to_budget (
2394       p_adj_amt_tbl         IN  ozf_adjusted_amt_tbl_type,
2395       x_return_status       OUT NOCOPY      VARCHAR2,
2396       x_msg_count           OUT NOCOPY      NUMBER,
2397       x_msg_data            OUT NOCOPY      VARCHAR2
2398    ) IS
2399       l_return_status           VARCHAR2(1);
2400       l_offer_name              VARCHAR2(240);
2401       l_adj_amount              NUMBER;
2402       l_remaining_amount        NUMBER;
2403       l_rate                    NUMBER;
2404       l_converted_adj_amount    NUMBER;
2405       l_act_util_rec            ozf_actbudgets_pvt.act_util_rec_type;
2406       l_act_budgets_rec         ozf_actbudgets_pvt.act_budgets_rec_type;
2407       l_util_rec                ozf_fund_utilized_pvt.utilization_rec_type;
2408       l_fund_amt_tbl            ozf_fund_amt_tbl_type;
2409       l_cust_account_id         NUMBER;
2410       l_adjustment_date         DATE;
2411       l_bill_to_site_use_id     NUMBER;
2412       l_ship_to_site_use_id     NUMBER;
2413       l_utilization_id          NUMBER;
2414 
2415       l_order_org_id            NUMBER;
2416       l_exchange_rate_type      VARCHAR2(30) := FND_API.G_MISS_CHAR ;
2417 
2418        -- Added by rimehrot for R12
2419       CURSOR c_get_price_adj_dtl (p_price_adjustment_id IN NUMBER) IS
2420          SELECT creation_date
2421            FROM oe_price_adjustments adj
2422            WHERE adj.price_Adjustment_id = p_price_adjustment_id;
2423 
2424       CURSOR c_cust_number (p_header_id IN NUMBER) IS
2425          SELECT cust.cust_account_id, header.invoice_to_org_id, header.ship_to_org_id
2426            FROM hz_cust_acct_sites_all acct_site,
2427                 hz_cust_site_uses_all site_use,
2428                 hz_cust_accounts  cust,
2429                 oe_order_headers_all header
2430           WHERE header.header_id = p_header_id
2431               AND acct_site.cust_acct_site_id = site_use.cust_acct_site_id
2432             AND acct_site.cust_account_id = cust.cust_account_id
2433             AND site_use.site_use_id = header.invoice_to_org_id ;
2434 
2435       --Added for bug 7030415, get order's org_id
2436       CURSOR c_order_org_id (p_line_id IN NUMBER) IS
2437          SELECT header.org_id
2438          FROM oe_order_lines_all line, oe_order_headers_all header
2439          WHERE line_id = p_line_id
2440          AND line.header_id = header.header_id;
2441 
2442       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
2443          SELECT beneficiary_account_id,
2444                autopay_party_attr,autopay_party_id,transaction_currency_code
2445            FROM ozf_offers
2446           WHERE qp_list_header_id = p_offer_id;
2447 
2448       --Added for bug 7030415, get conversion type
2449       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
2450          SELECT exchange_rate_type
2451          FROM   ozf_sys_parameters_all
2452          WHERE  org_id = p_org_id;
2453 
2454      --Added c_site_org_id for bug 6278466
2455       CURSOR c_site_org_id (p_site_use_id IN NUMBER) IS
2456          SELECT org_id
2457            FROM hz_cust_site_uses_all
2458           WHERE site_use_id = p_site_use_id;
2459 
2460       l_offer_type  c_offer_type%ROWTYPE;
2461 
2462 
2463    BEGIN
2464      x_return_status            := fnd_api.g_ret_sts_success;
2465 
2466      IF g_debug_flag = 'Y' THEN
2467         ozf_utility_pvt.write_conc_log('    D: Enter post_accrual_to_budget   p_adj_amt_tbl count=' || p_adj_amt_tbl.count);
2468      END IF;
2469 
2470      FOR i IN p_adj_amt_tbl.FIRST .. p_adj_amt_tbl.LAST
2471      LOOP
2472 
2473         IF g_debug_flag = 'Y' THEN
2474            ozf_utility_pvt.write_conc_log('D: Enter post_accrual_to_budget   price_adj_id=' || p_adj_amt_tbl(i).price_adjustment_id ||
2475                            ' amount=' || p_adj_amt_tbl(i).earned_amount);
2476         END IF;
2477 
2478         l_fund_amt_tbl.DELETE;
2479 
2480         OPEN c_cust_number(p_adj_amt_tbl(i).order_header_id);
2481         FETCH c_cust_number INTO l_cust_account_id, l_bill_to_site_use_id, l_ship_to_site_use_id;
2482         CLOSE c_cust_number;
2483 
2484         ozf_accrual_engine.calculate_accrual_amount (
2485           x_return_status  => l_return_status,
2486           p_src_id         => p_adj_amt_tbl(i).qp_list_header_id,
2487           p_earned_amt     => p_adj_amt_tbl(i).earned_amount,
2488           p_cust_account_type => 'BILL_TO',
2489           p_cust_account_id => l_cust_account_id,
2490           p_product_item_id => p_adj_amt_tbl(i).product_id,
2491           x_fund_amt_tbl   => l_fund_amt_tbl
2492         );
2493 
2494         IF g_debug_flag = 'Y' THEN
2495            ozf_utility_pvt.write_conc_log ('    D: post_adjust_to_budget(): Calculate Accrual Amount returns' || l_return_status);
2496         END IF;
2497 
2498         IF l_return_status <> fnd_api.g_ret_sts_success THEN
2499            IF l_return_status = fnd_api.g_ret_sts_error THEN
2500               RAISE fnd_api.g_exc_error;
2501            ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
2502               RAISE fnd_api.g_exc_unexpected_error;
2503            END IF;
2504         END IF;
2505 
2506         --- if this is not funded by a parent campaign or any budget the error OUT NOCOPY saying no budgte found
2507         IF l_fund_amt_tbl.COUNT = 0 THEN
2508            IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
2509               fnd_message.set_name ('OZF', 'OZF_FUND_NO_BUDGET_FOUND');
2510               fnd_message.set_token ('OFFER_ID', p_adj_amt_tbl(i).qp_list_header_id);
2511               fnd_msg_pub.ADD;
2512            END IF;
2513            IF g_debug_flag = 'Y' THEN
2514               ozf_utility_pvt.write_conc_log('    D: post_adjust_to_budget()  calculation for posting to budget failed. No posting to budget. RETURN');
2515            END IF;
2516            -- yzhao: 03/26/2003 should continue or error out?
2517            --RETURN;
2518            --kdass 24-MAR-2007 bug 5900966 - if no budget is attached to the offer, then move to process next record
2519            GOTO l_endofadjamtloop;
2520         END IF;
2521 
2522         l_adj_amount := 0; -- in offer currency
2523         l_remaining_amount  := p_adj_amt_tbl(i).earned_amount; -- in offer currency
2524 
2525         IF g_debug_flag = 'Y' THEN
2526            ozf_utility_pvt.write_conc_log (' D: post_adjust_to_budget() Begin loop l_remaining_amount '|| l_remaining_amount || ' l_adj amount ' || l_adj_amount);
2527         END IF;
2528 
2529         -- added by rimehrot for R12
2530         OPEN c_get_price_adj_dtl (p_adj_amt_tbl(i).price_adjustment_id);
2531         FETCH c_get_price_adj_dtl INTO l_adjustment_date;
2532         CLOSE c_get_price_adj_dtl;
2533 
2534         FOR j IN l_fund_amt_tbl.FIRST .. l_fund_amt_tbl.LAST
2535         LOOP
2536            l_act_budgets_rec :=NULL;
2537            l_util_rec :=NULL;
2538 
2539            -- nepanda : changed the below to check with Absolute value to take care of -ve accruals.
2540            -- For negative accruals(RMA Orders), fraction was not taken into consideration when there are more than one budgets in the offer.
2541            IF ABS(l_remaining_amount) >= ABS(l_fund_amt_tbl (j).earned_amount) THEN
2542              l_adj_amount := l_fund_amt_tbl (j).earned_amount; -- this is in offer and order currency
2543            ELSE
2544              l_adj_amount := l_remaining_amount;
2545            END IF;
2546            l_remaining_amount := l_remaining_amount - l_adj_amount;
2547 
2548            --nirprasa, ER 8399134,multi-currency enhancement the amount is in order currency now.
2549            --IF p_adj_amt_tbl(i).offer_currency = l_fund_amt_tbl (j).budget_currency THEN
2550            IF p_adj_amt_tbl(i).order_currency = l_fund_amt_tbl (j).budget_currency THEN
2551               l_act_budgets_rec.parent_src_apprvd_amt :=l_adj_amount;
2552            ELSE
2553               IF g_debug_flag = 'Y' THEN
2554                  ozf_utility_pvt.write_conc_log ('    D: post_adjust_to_budget() In not equal currency');
2555               END IF;
2556 
2557               -- Added for bug 7030415, get the order's org_id to get the exchange rate.
2558 
2559               /*Adjustment amount is converted from plan curr to budgets curr to populate
2560               parent_src_apprvd_amt column in ozf_act_budgets table and amount column
2561               of ozf_funds_utilized_all_b table*/
2562 
2563                  OPEN c_order_org_id(p_adj_amt_tbl(i).order_line_id);
2564                  FETCH c_order_org_id INTO l_order_org_id;
2565                  CLOSE c_order_org_id;
2566 
2567                  OPEN c_offer_type(p_adj_amt_tbl(i).qp_list_header_id);
2568                  FETCH c_offer_type INTO l_offer_type;
2569                  CLOSE c_offer_type;
2570 
2571                  IF l_util_rec.cust_account_id IS NULL THEN
2572                    IF l_offer_type.beneficiary_account_id IS NOT NULL THEN
2573                     IF l_offer_type.autopay_party_attr <> 'CUSTOMER' AND l_offer_type.autopay_party_attr IS NOT NULL THEN
2574 
2575                       OPEN c_site_org_id (l_offer_type.autopay_party_id);
2576                       FETCH c_site_org_id INTO l_order_org_id;
2577                       CLOSE c_site_org_id;
2578 
2579                         END IF;
2580                     END IF;
2581                 END IF;
2582 
2583                  OPEN c_get_conversion_type(l_order_org_id);
2584                  FETCH c_get_conversion_type INTO l_exchange_rate_type;
2585                  CLOSE c_get_conversion_type;
2586 
2587                 IF g_debug_flag = 'Y' THEN
2588                   ozf_utility_pvt.write_conc_log('**************************START****************************');
2589                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' From Amount l_adj_amount: '||l_adj_amount );
2590                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' From Curr p_adj_amt_tbl(i).offer_currency: '||p_adj_amt_tbl(i).offer_currency );
2591                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' From Curr p_adj_amt_tbl(i).order_currency '||p_adj_amt_tbl(i).order_currency );
2592                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' To Curr l_fund_amt_tbl (j).budget_currency: '|| l_fund_amt_tbl (j).budget_currency);
2593                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' l_exchange_rate_type: '|| l_exchange_rate_type);
2594                 END IF;
2595 
2596               --nirprasa, ER 8399134 added if condition for null currency offer case where source currency for conversions will be order currency
2597               --and else condition to hadle arrows case when offer's currency is
2598               --different from order currency, in which case the source currency for conversions will be offer currency
2599               IF l_offer_type.transaction_currency_code IS NULL THEN
2600               ozf_utility_pvt.convert_currency (
2601                x_return_status => l_return_status,
2602                p_from_currency => p_adj_amt_tbl(i).order_currency,
2603                p_to_currency   => l_fund_amt_tbl (j).budget_currency,
2604                p_conv_type     => l_exchange_rate_type, -- nirprasa added for bug 7030415
2605                p_from_amount   => l_adj_amount,
2606                x_to_amount     => l_converted_adj_amount,
2607                x_rate          => l_rate
2608               );
2609               ELSE
2610               ozf_utility_pvt.convert_currency (
2611                x_return_status => l_return_status,
2612                p_from_currency => p_adj_amt_tbl(i).offer_currency,
2613                p_to_currency   => l_fund_amt_tbl (j).budget_currency,
2614                p_conv_type     => l_exchange_rate_type, -- nirprasa added for bug 7030415
2615                p_from_amount   => l_adj_amount,
2616                x_to_amount     => l_converted_adj_amount,
2617                x_rate          => l_rate
2618               );
2619               END IF;
2620 
2621                IF g_debug_flag = 'Y' THEN
2622                 ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' Converted Amount l_converted_adj_amount: '|| l_converted_adj_amount);
2623                 ozf_utility_pvt.write_conc_log('Adjustment amount is converted from offer curr to budgets curr to populate parent_src_apprvd_amt column in izf_act_budgets table and amount column of ozf_funds_utilized_all_b table');
2624                 ozf_utility_pvt.write_conc_log('***************************END******************************');
2625               END IF;
2626 
2627               IF l_return_status <> fnd_api.g_ret_sts_success THEN
2628                  IF g_debug_flag = 'Y' THEN
2629                     ozf_utility_pvt.write_conc_log ('   D: post_adjust_to_budget() convert currency failed. No posting to budget. Return');
2630                  END IF;
2631                  RAISE fnd_api.g_exc_unexpected_error;
2632               END IF;
2633               l_act_budgets_rec.parent_src_apprvd_amt :=l_converted_adj_amount;
2634            END IF;
2635 
2636            IF g_debug_flag = 'Y' THEN
2637               ozf_utility_pvt.write_conc_log (   '    D: post_adjust_to_budget() Adj amount coverted ' || l_converted_adj_amount
2638               || ' l_adj amount '     || l_adj_amount        );
2639            END IF;
2640 
2641            l_act_budgets_rec.budget_source_type := 'OFFR';
2642            l_act_budgets_rec.budget_source_id := p_adj_amt_tbl(i).qp_list_header_id;
2643            l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
2644            l_act_budgets_rec.act_budget_used_by_id := p_adj_amt_tbl(i).qp_list_header_id;
2645            l_act_budgets_rec.parent_src_curr := l_fund_amt_tbl (j).budget_currency;
2646            l_act_budgets_rec.parent_source_id := l_fund_amt_tbl (j).ofr_src_id;
2647            l_act_budgets_rec.request_amount :=l_adj_amount;
2648            --nirprasa, ER 8399134 multi currency enhancement
2649            --l_act_budgets_rec.request_currency := p_adj_amt_tbl(i).offer_currency;
2650            --nirprasa, ER 8399134 multi currency enhancement
2651            IF l_offer_type.transaction_currency_code IS NULL THEN
2652               l_act_budgets_rec.request_currency := p_adj_amt_tbl(i).order_currency;
2653            ELSE
2654               l_act_budgets_rec.request_currency := p_adj_amt_tbl(i).offer_currency;
2655            END IF;
2656            l_act_budgets_rec.approved_amount := l_act_budgets_rec.request_amount;
2657            --nirprasa, ER 8399134 multi currency enhancement
2658            --l_act_budgets_rec.approved_in_currency := p_adj_amt_tbl(i).offer_currency;
2659            l_act_budgets_rec.approved_in_currency := l_act_budgets_rec.request_currency;
2660            -- added by rimehrot for R12
2661            l_util_rec.bill_to_site_use_id := l_bill_to_site_use_id;
2662            l_util_rec.ship_to_site_use_id := l_ship_to_site_use_id;
2663            l_util_rec.billto_cust_account_id := l_cust_account_id;
2664            l_util_rec.adjustment_date := l_adjustment_date;
2665            l_util_rec.object_type := 'ORDER';
2666            l_util_rec.object_id   := p_adj_amt_tbl(i).order_header_id;
2667            l_util_rec.price_adjustment_id := p_adj_amt_tbl(i).price_adjustment_id;
2668            l_util_rec.amount := l_act_budgets_rec.parent_src_apprvd_amt;
2669            l_util_rec.plan_curr_amount := l_act_budgets_rec.request_amount;
2670            l_util_rec.component_type := 'OFFR';
2671            l_util_rec.component_id := p_adj_amt_tbl(i).qp_list_header_id ;
2672            l_util_rec.currency_code := l_fund_amt_tbl (j).budget_currency;
2673            l_util_rec.fund_id := l_fund_amt_tbl(j).ofr_src_id;
2674            l_util_rec.product_id := p_adj_amt_tbl(i).product_id ;
2675            l_util_rec.volume_offer_tiers_id := NULL;
2676            l_util_rec.gl_posted_flag := G_GL_FLAG_NO;  -- 'N'
2677            l_util_rec.billto_cust_account_id := l_cust_account_id;
2678            l_util_rec.order_line_id := p_adj_amt_tbl(i).order_line_id;
2679            --nirprasa, ER 8399134multi currency enhancement
2680            l_util_rec.plan_currency_code := l_act_budgets_rec.request_currency;
2681            l_util_rec.fund_request_currency_code := p_adj_amt_tbl(i).offer_currency;
2682            --nirprasa, ER 8399134 multi currency enhancement
2683            l_util_rec.cost_price := p_adj_amt_tbl(i).cost_price;
2684            l_util_rec.cost_price_currency_code := p_adj_amt_tbl(i).cost_price_currency_code;
2685 
2686            create_fund_utilization (
2687                 p_act_util_rec     => l_util_rec,
2688                 p_act_budgets_rec  => l_act_budgets_rec,
2689                 x_utilization_id   => l_utilization_id,
2690                 x_return_status    => l_return_status,
2691                 x_msg_count        => x_msg_count,
2692                 x_msg_data         => x_msg_data
2693               );
2694            IF l_return_status <> fnd_api.g_ret_sts_success THEN
2695               IF g_debug_flag = 'Y' THEN
2696                  ozf_utility_pvt.write_conc_log ('D: post_adjust_to_budget() create_fund_utilization() returns error. Exception');
2697               END IF;
2698               RAISE fnd_api.g_exc_unexpected_error;
2699            END IF;
2700 
2701            <<l_endofearadjloop>>
2702 
2703            IF g_debug_flag = 'Y' THEN
2704               ozf_utility_pvt.write_conc_log ( '    D: post_adjust_to_budget()  loop iteration end l_remaining_amount ' || l_remaining_amount
2705                 || ' l_adj amount '|| l_adj_amount || ' fund_id '
2706                 || l_fund_amt_tbl (j).ofr_src_id        );
2707            END IF;
2708 
2709            EXIT WHEN l_remaining_amount = 0;
2710         END LOOP earned_adj_loop;
2711 
2712         <<l_endofadjamtloop>>
2713 
2714         IF g_debug_flag = 'Y' THEN
2715            ozf_utility_pvt.write_conc_log('D: Ends successfully post_accrual_to_budget   price_adj_id=' || p_adj_amt_tbl(i).price_adjustment_id
2716                   || ' amount=' || p_adj_amt_tbl(i).earned_amount);
2717         END IF;
2718 
2719      END LOOP; -- p_adj_amt_tbl
2720 
2721      IF g_debug_flag = 'Y' THEN
2722         ozf_utility_pvt.write_conc_log('D: Ends of post_accrual_to_budget');
2723      END IF;
2724 
2725      x_return_status   := fnd_api.g_ret_sts_success;
2726 
2727      fnd_msg_pub.count_and_get (
2728             p_count=> x_msg_count,
2729             p_data=> x_msg_data,
2730             p_encoded=> fnd_api.g_false
2731          );
2732 
2733    EXCEPTION
2734       --nepanda : Added exception block for normal errors and unexpected errors, before checking for OTHERS
2735       WHEN fnd_api.g_exc_error THEN
2736          x_return_status            := fnd_api.g_ret_sts_error;
2737          ozf_utility_pvt.write_conc_log (' /**************EXCEPTION in ozf_accrual_engine.post_accrual_to_budget');
2738          fnd_msg_pub.count_and_get (
2739             p_count=> x_msg_count,
2740             p_data=> x_msg_data,
2741             p_encoded=> fnd_api.g_false
2742          );
2743       WHEN fnd_api.g_exc_unexpected_error THEN
2744          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2745          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2746             fnd_msg_pub.add_exc_msg ('ozf_accrual_engine', 'post_accrual_to_budget');
2747          END IF;
2748         ozf_utility_pvt.write_conc_log (' /**************UNEXPECTED EXCEPTION in ozf_accrual_engine.post_accrual_to_budget');
2749         fnd_msg_pub.count_and_get (
2750             p_count=> x_msg_count,
2751             p_data=> x_msg_data,
2752             p_encoded=> fnd_api.g_false
2753          );
2754       WHEN OTHERS THEN
2755         x_return_status            := fnd_api.g_ret_sts_unexp_error;
2756         IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2757            fnd_msg_pub.add_exc_msg ('ozf_accrual_engine', 'post_accrual_to_budget');
2758         END IF;
2759         ozf_utility_pvt.write_conc_log (' /**************UNEXPECTED EXCEPTION in ozf_accrual_engine.post_accrual_to_budget');
2760         fnd_msg_pub.count_and_get (
2761             p_count=> x_msg_count,
2762             p_data=> x_msg_data,
2763             p_encoded=> fnd_api.g_false
2764          );
2765   END post_accrual_to_budget;
2766 
2767 ------------------------------------------------------------------------------
2768 -- Procedure Name
2769 --   Adjust_Accrual
2770 -- Purpose
2771 --   This procedure will calculate and update the accrual info.
2772 --
2773 --  created      pjindal     06/20/00
2774 --  updated      mpande      07/18/00
2775 --  updated      mpande      08/02/00 -- changed the fund_utlization creation calls
2776 --  updated      mpande      02/02/01 -- changed the fund_type checks , benifit  limit checks
2777 --  updated      mpande      12/28/2001  -- added line and header info also
2778 ------------------------------------------------------------------------------
2779    PROCEDURE adjust_accrual (
2780       p_api_version        IN       NUMBER,
2781       p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false,
2782       p_commit             IN       VARCHAR2 := fnd_api.g_false,
2783       p_validation_level   IN       NUMBER := fnd_api.g_valid_level_full,
2784       x_return_status      OUT NOCOPY      VARCHAR2,
2785       x_msg_count          OUT NOCOPY      NUMBER,
2786       x_msg_data           OUT NOCOPY      VARCHAR2,
2787       p_line_adj_tbl       IN       oe_order_pub.line_adj_tbl_type,
2788       p_old_line_adj_tbl   IN       oe_order_pub.line_adj_tbl_type,
2789       p_header_rec         IN       oe_order_pub.header_rec_type := NULL,
2790       p_exception_queue    IN       VARCHAR2 := fnd_api.g_false
2791 
2792    ) IS
2793       l_return_status           VARCHAR2 (10)                           := fnd_api.g_ret_sts_success;
2794       l_api_name       CONSTANT VARCHAR2 (30)                           := 'Adjust_Accrual';
2795       l_api_version    CONSTANT NUMBER                                  := 1.0;
2796       l_earned_amount           NUMBER;
2797       l_old_earned_amount       NUMBER;
2798       l_util_id                 NUMBER;
2799       l_adj_amount              NUMBER;
2800       l_line_quantity           NUMBER;
2801       l_old_adjusted_amount     NUMBER    := 0;
2802       l_cancelled_quantity      NUMBER;
2803       l_modifier_level_code     VARCHAR2 (30);
2804       l_new_adjustment_amount   NUMBER;
2805       l_line_category_code      VARCHAR2(30);
2806       l_range_break             NUMBER;
2807       l_operation               VARCHAR2(30);
2808       l_product_id              NUMBER;
2809       l_util_rec                ozf_fund_utilized_pvt.utilization_rec_type;
2810       l_act_budgets_rec         ozf_actbudgets_pvt.act_budgets_rec_type;
2811       l_gl_posted_flag          VARCHAR2 (1);
2812       l_utilization_id          NUMBER;
2813       l_gl_date                 DATE;
2814       l_object_version_number   NUMBER;
2815       l_plan_type               VARCHAR2(30);
2816       l_utilization_type        VARCHAR2(30);
2817       l_amount                  NUMBER;
2818       l_fund_id                 NUMBER;
2819       l_acctd_amount            NUMBER;
2820       l_order_curr              VARCHAR2(30);
2821       l_offer_curr              VARCHAR2(30);
2822       l_count                   NUMBER            := 0;
2823       l_adj_amt_tbl             ozf_adjusted_amt_tbl_type;
2824       l_plan_id                 NUMBER;
2825       l_plan_amount             NUMBER;
2826       l_rate                    NUMBER;
2827       l_conv_earned_amount      NUMBER;
2828       l_conv_adjustment_amount  NUMBER;
2829       l_util_exists             NUMBER;
2830       l_new_line_id             NUMBER;
2831 
2832       l_order_org_id            NUMBER;
2833       l_exchange_rate_type      VARCHAR2(30) := FND_API.G_MISS_CHAR;
2834       l_offer_transaction_curr  VARCHAR2(30);
2835 
2836       CURSOR c_line_info (p_line_id IN NUMBER) IS
2837          SELECT line.inventory_item_id,
2838                 line.ordered_quantity,
2839                 line.cancelled_quantity,
2840                 line.line_category_code,
2841                 header.transactional_curr_code,
2842                 header.org_id,
2843        		line.shipping_quantity,      -- Catch Weight ER
2844        		line.shipping_quantity_uom,  -- Catch Weight ER
2845 	        line.shipping_quantity2,     -- Catch Weight ER
2846 		line.shipping_quantity_uom2, -- Catch Weight ER
2847 		line.fulfillment_base,       -- Catch Weight ER
2848 		line.order_quantity_uom      -- Catch Weight ER
2849          FROM oe_order_lines_all line, oe_order_headers_all header
2850          WHERE line_id = p_line_id
2851            AND line.header_id = header.header_id;
2852 
2853      -- Catch Weight ER - start
2854      l_cw_quantity NUMBER;
2855      l_cw_quantity_uom VARCHAR(10);
2856      l_shipping_quantity NUMBER;
2857      l_shipping_quantity_uom VARCHAR(10);
2858      l_shipping_quantity2 NUMBER;
2859      l_shipping_quantity_uom2 VARCHAR(10);
2860      l_fulfillment_base  VARCHAR2(1);
2861      l_order_quantity_uom VARCHAR(10);
2862      -- Catch Weight ER - end
2863 
2864       CURSOR c_list_line_info (p_list_line_id IN NUMBER) IS
2865          SELECT estim_gl_value
2866          FROM qp_list_lines
2867          WHERE list_line_id = p_list_line_id;
2868 
2869       CURSOR c_old_adjustment_amount (p_price_adjustment_id IN NUMBER) IS
2870          SELECT SUM (plan_curr_amount)
2871          FROM ozf_funds_utilized_all_b
2872          WHERE price_adjustment_id = p_price_adjustment_id
2873          AND object_type = 'ORDER';
2874 
2875       CURSOR c_order_count (p_header_id IN NUMBER) IS
2876          SELECT SUM (ordered_quantity - NVL (cancelled_quantity, 0))
2877          FROM oe_order_lines_all
2878          WHERE header_id = p_header_id;
2879 
2880          -- Added adjusted_amount for bug fix 4173825
2881       CURSOR c_mod_level (p_price_ad_id IN NUMBER) IS
2882          SELECT modifier_level_code,range_break_quantity, adjusted_amount, operand, arithmetic_operator --ER9447673
2883          FROM oe_price_adjustments
2884          WHERE price_adjustment_id = p_price_ad_id;
2885 
2886          l_operand NUMBER;
2887          l_arithmetic_operator VARCHAR2(30);
2888 
2889       -- Added component_type,utilization_type for bug fix 5523042
2890       CURSOR c_old_adjustment_amt (p_price_adjustment_id IN NUMBER) IS
2891          SELECT  NVL (amount, 0) amount,
2892                   fund_id,
2893                   currency_code,
2894                   NVL (plan_curr_amount, 0) plan_curr_amount,
2895                   gl_posted_flag, product_id,component_type,utilization_type,
2896                   NVL (fund_request_amount, 0) fund_request_amount,plan_currency_code,fund_request_currency_code --nirprasa, ER 8399134, multi-currency enhancement
2897          FROM ozf_funds_utilized_all_b
2898          WHERE price_adjustment_id = p_price_adjustment_id
2899          AND object_type = 'ORDER';
2900          --GROUP BY fund_id, currency_code, price_adjustment_id, gl_posted_flag, product_id ;
2901 
2902       --nirprasa, ER 8399134 query fund_request_amount instead of plan_curr_amount
2903       CURSOR c_get_util_rec(p_utilization_id IN NUMBER) IS
2904        SELECT  object_version_number,
2905                plan_type, utilization_type,
2906                amount,
2907                fund_id,
2908                acctd_amount,
2909                plan_id,
2910                fund_request_amount
2911        FROM   ozf_funds_utilized_all_b
2912        WHERE  utilization_id = p_utilization_id;
2913 
2914       CURSOR c_tm_offer (p_list_header_id IN NUMBER) IS
2915          --SELECT nvl(transaction_currency_code,fund_request_curr_code) transaction_currency_code
2916          SELECT nvl(transaction_currency_code,fund_request_curr_code) offer_currency_code,
2917                 transaction_currency_code
2918          FROM ozf_offers
2919          WHERE qp_list_header_id = p_list_header_id;
2920 
2921       CURSOR c_get_util (p_list_header_id IN NUMBER, p_header_id IN NUMBER, p_line_id IN NUMBER) IS
2922          SELECT 1
2923          FROM ozf_funds_utilized_all_b
2924          WHERE plan_type = 'OFFR'
2925          AND plan_id = p_list_header_id
2926          AND object_type = 'ORDER'
2927          AND object_id = p_header_id
2928          AND order_line_id = p_line_id
2929          AND utilization_type = 'ADJUSTMENT'
2930          AND price_adjustment_id IS NULL;
2931 
2932       CURSOR c_split_line(p_line_id IN NUMBER) IS
2933         SELECT line_id
2934         FROM oe_order_lines_all
2935         WHERE split_from_line_id IS NOT NULL
2936         AND line_id = p_line_id
2937         AND split_by = 'SYSTEM';
2938 
2939       -- added for bug 7030415 get conversion type
2940       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
2941          SELECT exchange_rate_type
2942          FROM   ozf_sys_parameters_all
2943          WHERE  org_id = p_org_id;
2944 
2945      CURSOR c_offer_details(p_qp_list_header_id NUMBER) IS
2946         SELECT  custom_setup_id, description
2947         FROM   ozf_offers off, qp_list_headers_all qp
2948         WHERE  off.qp_list_header_id = p_qp_list_header_id
2949         AND off.qp_list_header_id = qp.list_header_id;
2950 
2951      CURSOR c_is_parent_line (p_line_id IN NUMBER) IS
2952         SELECT 1
2953         FROM oe_order_lines_all
2954         WHERE split_from_line_id = p_line_id;
2955 
2956      l_is_parent_line NUMBER;
2957 
2958    c_purchase_price purchase_price_cursor_type;
2959 
2960 
2961    l_cost_price NUMBER;
2962    l_custom_setup_id NUMBER;
2963    l_offer_name VARCHAR2(2000);
2964    l_column_name VARCHAR2(15);
2965    l_stmt VARCHAR2(3000);
2966 
2967       BEGIN
2968          SAVEPOINT adjust_accrual;
2969          -- Standard call to check for call compatibility.
2970          IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
2971             RAISE fnd_api.g_exc_unexpected_error;
2972          END IF;
2973          -- Initialize message list IF p_init_msg_list is set to TRUE.
2974          IF fnd_api.to_boolean (p_init_msg_list) THEN
2975             fnd_msg_pub.initialize;
2976          END IF;
2977          --  Initialize API return status to success
2978          x_return_status            := fnd_api.g_ret_sts_success;
2979 
2980          <<new_line_tbl_loop>>
2981 
2982          IF g_debug_flag = 'Y' THEN
2983             ozf_utility_pvt.write_conc_log ('  D: Inside New Line Table Loop');
2984          END IF;
2985 
2986          l_adj_amt_tbl.DELETE;
2987 
2988          FOR i IN NVL (p_line_adj_tbl.FIRST, 1) .. NVL (p_line_adj_tbl.LAST, 0)
2989          LOOP
2990             x_return_status            := fnd_api.g_ret_sts_success;
2991             SAVEPOINT line_adjustment;
2992 
2993             IF g_debug_flag = 'Y' THEN
2994               ozf_utility_pvt.write_conc_log ('    /++++++++ ADJUSTMENT DEBUG MESSAGE START +++++++++/'          );
2995               ozf_utility_pvt.write_conc_log ('    D: Begin Processing For Price Adjustment Id # '|| p_line_adj_tbl(i).price_adjustment_id          );
2996             END IF;
2997 
2998             IF  p_line_adj_tbl (i).list_line_type_code IN
2999                                               ('CIE', 'DIS', 'IUE', 'OID',  'PLL', 'PMR', 'TSN','PBH')
3000                 --AND p_line_adj_tbl (i).applied_flag = 'Y'
3001                 AND p_line_adj_tbl (i).applied_flag IN ('Y', 'N') --bug 8253115
3002            THEN
3003 
3004               OPEN c_tm_offer ( p_line_adj_tbl (i).list_header_id);
3005               FETCH c_tm_offer INTO l_offer_curr,l_offer_transaction_curr;
3006 
3007             -- check if it is a TM Offers
3008               IF c_tm_offer%NOTFOUND THEN
3009                  CLOSE c_tm_offer;
3010                  IF g_debug_flag = 'Y' THEN
3011                     ozf_utility_pvt.write_conc_log('D  not TM offer: offer id:  ' ||  p_line_adj_tbl(i).list_header_id);
3012                  END IF;
3013                  GOTO l_endoflineadjloop;
3014               ELSE
3015                  CLOSE c_tm_offer;
3016               END IF;
3017 
3018               l_line_quantity            := 0;
3019               l_old_adjusted_amount      := 0;
3020               l_cancelled_quantity       := 0;
3021               l_earned_amount            := 0;
3022               l_new_adjustment_amount    := 0; --nirprasa, fix for bug 8435499.
3023               l_cost_price := 0;
3024 
3025               IF g_debug_flag = 'Y' THEN
3026                  ozf_utility_pvt.write_conc_log ('    D: Operation '|| p_line_adj_tbl (i).operation ||
3027                  ' Order header id  ' || p_line_adj_tbl (i).header_id || ' Line id  ' || p_line_adj_tbl (i).line_id  ||
3028                   ' applied flag  ' || p_line_adj_tbl (i).applied_flag);
3029               END IF;
3030 
3031               OPEN c_line_info (p_line_adj_tbl (i).line_id);
3032               FETCH c_line_info INTO l_product_id,
3033                                      l_line_quantity,
3034                                      l_cancelled_quantity,
3035                                      l_line_category_code,
3036                                      l_order_curr,
3037                                      l_order_org_id,
3038                                      l_shipping_quantity,     -- Catch Weight ER
3039                                      l_shipping_quantity_uom, -- Catch Weight ER
3040                                      l_shipping_quantity2,     -- Catch Weight ER
3041                                      l_shipping_quantity_uom2, -- Catch Weight ER
3042 				     l_fulfillment_base,       -- Catch Weight ER
3043 				     l_order_quantity_uom;    -- Catch Weight ER
3044               CLOSE c_line_info;
3045 
3046                --Added for bug 7030415
3047               OPEN c_get_conversion_type(l_order_org_id);
3048               FETCH c_get_conversion_type INTO l_exchange_rate_type;
3049               CLOSE c_get_conversion_type;
3050 
3051               --bug 8253115 - Negative accruals are not created for manually deleted modifiers.
3052               --When modifiers are deleted manually from booked orders, we get UPDATE message with applied_flag = N
3053               --instead of DELETE message with applied_flag = Y, so for this record changed the operation to DELETE
3054               IF p_exception_queue = fnd_api.g_true AND p_line_adj_tbl (i).operation = 'CREATE' THEN
3055                  l_operation := 'UPDATE' ;
3056               ELSIF p_line_adj_tbl (i).operation = 'UPDATE' AND p_line_adj_tbl (i).applied_flag = 'N' THEN
3057                  l_operation := 'DELETE';
3058               ELSIF p_line_adj_tbl (i).applied_flag = 'Y' THEN
3059                  l_operation := p_line_adj_tbl (i).operation;
3060               ELSE
3061                  GOTO l_endoflineadjloop;
3062               END IF;
3063 
3064               IF l_operation <> 'DELETE' THEN
3065                  OPEN c_mod_level (p_line_adj_tbl (i).price_adjustment_id);
3066                  FETCH c_mod_level INTO l_modifier_level_code,l_range_break, l_new_adjustment_amount,l_operand, l_arithmetic_operator; --ER9447673;
3067                  CLOSE c_mod_level;
3068 
3069                  IF g_debug_flag = 'Y' THEN
3070                     ozf_utility_pvt.write_conc_log ('    D: Modifier level code '|| l_modifier_level_code);
3071                  END IF;
3072               END IF;
3073 
3074               IF g_debug_flag = 'Y' THEN
3075                  ozf_utility_pvt.write_conc_log (
3076                   '    D: Line quantity '|| l_line_quantity || ' Cancelled quantity ' || l_cancelled_quantity ||
3077                   '   line_adj_tbl.adjusted_amount=' || l_new_adjustment_amount
3078                  );
3079               END IF;
3080 
3081               IF l_modifier_level_code = 'ORDER' THEN
3082                   -- for the time being this is the workaround cause there is no way to find out how much adjustment for total
3083                   -- has happened due to this order level offer
3084                  l_cancelled_quantity       := 0;
3085                  OPEN c_order_count (p_line_adj_tbl (i).header_id);
3086                  FETCH c_order_count INTO l_line_quantity;
3087                  CLOSE c_order_count;
3088               END IF;
3089 
3090               --kdass 24-FEB-07 bug 5485334 - do not create utilization when offer gets applied on
3091               --order booked before offer start date on manual re-pricing order
3092               OPEN c_get_util (p_line_adj_tbl(i).list_header_id, p_line_adj_tbl(i).header_id, p_line_adj_tbl(i).line_id);
3093               FETCH c_get_util INTO l_util_exists;
3094               CLOSE c_get_util;
3095 
3096               IF NVL(l_util_exists,0) = 1 THEN
3097                  IF g_debug_flag = 'Y' THEN
3098                     ozf_utility_pvt.write_conc_log('Manual re-pricing of order created before offer start date. No utilization.');
3099                  END IF;
3100                  GOTO l_endoflineadjloop;
3101               END IF;
3102 
3103               IF l_operation = 'CREATE' THEN
3104                  IF g_debug_flag = 'Y' THEN
3105                     ozf_utility_pvt.write_conc_log ('operation create');
3106                  END IF;
3107 
3108                  OPEN  c_offer_details(p_line_adj_tbl(i).list_header_id);
3109                  FETCH c_offer_details INTO  l_custom_setup_id, l_offer_name;
3110                  CLOSE c_offer_details;
3111 
3112                  /*If its SDR offer then set context to order's org. get profile value which stores the column name
3113                  of oe_order_lines_all where purchase price is stored. Using the column name generate a
3114                  dynamic sql and execute the ref cursor.*/
3115 
3116                  IF l_custom_setup_id = 118 THEN --ER9447673
3117                      MO_GLOBAL.set_policy_context('S', l_order_org_id);
3118                      l_column_name := FND_PROFILE.VALUE('OZF_ITEM_COST_COLUMN');
3119 
3120                      IF l_column_name IS NOT NULL AND l_column_name <> FND_API.G_MISS_CHAR THEN
3121                         l_stmt := 'SELECT ' || l_column_name ||' FROM oe_order_lines_all  WHERE line_id = :1 AND org_id = :2';
3122 
3123                         IF g_debug_flag = 'Y' THEN
3124                         ozf_utility_pvt.write_conc_log('Query to obtain purchase price '||l_stmt);
3125                         END IF;
3126 
3127                         OPEN c_purchase_price FOR l_stmt using p_line_adj_tbl(i).line_id, l_order_org_id;
3128                         FETCH c_purchase_price INTO l_cost_price;
3129                         CLOSE c_purchase_price;
3130                      END IF;
3131 
3132                       -- Catch Weight ER - start
3133                      IF g_debug_flag = 'Y' THEN
3134 			ozf_utility_pvt.write_conc_log('Order_quantity_uom=' || l_order_quantity_uom );
3135 			ozf_utility_pvt.write_conc_log('order_quantity=' || l_line_quantity );
3136 
3137                         ozf_utility_pvt.write_conc_log(' l_cost_price' || l_cost_price );
3138                       END IF;
3139                       -- Catch Weight ER - end
3140 
3141                      IF (l_cost_price = -1) THEN
3142                          IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_debug_low) THEN
3143                                  fnd_message.set_name('OZF', 'OZF_COST_PRICE_NOT_FOUND');
3144                                  FND_MESSAGE.Set_Token('OFFR',l_offer_name); --OR LIST_HEADER_ID?
3145                                  FND_MESSAGE.Set_Token('ORDER',p_line_adj_tbl(i).header_id);
3146                                  FND_MESSAGE.Set_Token('ITEM',l_product_id);
3147                                  FND_MESSAGE.Set_Token('TEXT',sqlerrm);
3148                                  fnd_msg_pub.add;
3149                          END IF;
3150                              GOTO l_endoflineadjloop;
3151                      END IF;
3152 
3153                      IF g_debug_flag = 'Y' THEN
3154                         ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_cost_price = ' || l_cost_price);
3155                         ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_line_quantity = ' || l_line_quantity);
3156                         ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_arithmetic_operator = ' || l_arithmetic_operator);
3157                         ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_operand = ' || l_operand);
3158                      END IF;
3159 
3160 		      -- Catch Weight ER - start
3161 		      -- Converting shipping quantity from shipping uom to order uom only when arithmatic op is not AMT, as in case of AMT, operand takes care of catch weight
3162 		      IF l_arithmetic_operator <> 'AMT' THEN
3163 			/*OZF_UTILITY_PVT.get_catch_weight_quantity (
3164                             p_inventory_item_id      =>   l_product_id,
3165                             p_order_line_id	         =>   p_line_adj_tbl (i).line_id,
3166                             x_return_status	         =>   l_return_status,
3167                             x_cw_quantity		         =>   l_cw_quantity,
3168                             x_cw_quantity_uom	       =>   l_cw_quantity_uom );*/
3169 
3170 			    -- getting fulfillment_base from OE API. In case of performance issue can think of using fulfillment_base from existing cursor
3171 			    l_fulfillment_base := OE_DUAL_UOM_UTIL.get_fulfillment_base(p_line_adj_tbl (i).line_id) ;
3172 
3173 			    IF l_fulfillment_base = 'S' THEN
3174 			       l_cw_quantity     := l_shipping_quantity;
3175 			       l_cw_quantity_uom := l_shipping_quantity_uom;
3176 			    ELSE
3177 			       l_cw_quantity     := NVL(l_shipping_quantity2, l_shipping_quantity);
3178 			       l_cw_quantity_uom := NVL(l_shipping_quantity_uom2, l_shipping_quantity_uom);
3179 			    END IF;
3180 
3181 			    -- Converting shipping quantity from shipping uom to order uom as cost price is as per order uom
3182 			      IF l_cw_quantity_uom IS NOT NULL AND l_cw_quantity_uom <> l_order_quantity_uom THEN
3183 				 l_line_quantity := inv_convert.inv_um_convert(
3184 							    l_product_id                             -- item_id
3185 							    ,NULL                                    -- precision
3186                         				    ,l_cw_quantity                           -- from_quantity
3187                         				    ,l_cw_quantity_uom                       -- from_unit
3188 							    ,l_order_quantity_uom                    -- to_unit
3189 							    ,NULL                                    -- from_name
3190 							    ,NULL                                    -- to_name
3191 							    );
3192 				 ozf_utility_pvt.write_conc_log(' Catch Weight   D: adjust_accrual()_ l_line_quantity = ' || l_line_quantity);
3193 			      END IF;
3194 			END IF;
3195 			-- Catch Weight ER - end
3196 
3197                      IF l_arithmetic_operator = '%' THEN
3198                          l_earned_amount := (NVL(l_operand, 0)) * l_cost_price / 100  * (l_line_quantity);
3199                      ELSIF l_arithmetic_operator = 'NEWPRICE' THEN
3200                          l_earned_amount := (l_cost_price - (NVL(l_operand, 0))) * (l_line_quantity);
3201                      ELSE
3202                          l_earned_amount := (NVL(l_operand, 0)) * l_line_quantity;
3203                      END IF;
3204 
3205                      IF g_debug_flag = 'Y' THEN
3206                      ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ create  earned amount = ' || l_earned_amount);
3207                      END IF;
3208                  ELSE
3209                         l_earned_amount := (-(NVL(l_new_adjustment_amount, 0))) * l_line_quantity;
3210                  END IF;
3211 
3212                  --l_earned_amount := (-(NVL(l_new_adjustment_amount, 0))) * l_line_quantity;
3213                  --ER9447673
3214 
3215                  IF g_debug_flag = 'Y' THEN
3216                     ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ create  earned amount = ' || l_earned_amount);
3217                  END IF;
3218 
3219                  IF l_line_category_code = 'RETURN' THEN
3220                     IF g_debug_flag = 'Y' THEN
3221                        ozf_utility_pvt.write_conc_log ( '   LINE IS RETURN  ');
3222                     END IF;
3223                     l_earned_amount := -l_earned_amount;
3224                  END IF;
3225 
3226                   -- if it is a TSN then get the gl value of the upgrade
3227                  IF p_line_adj_tbl (i).list_line_type_code = 'TSN' THEN
3228                     OPEN c_list_line_info (p_line_adj_tbl (i).list_line_id);
3229                     FETCH c_list_line_info INTO l_earned_amount;
3230                     CLOSE c_list_line_info;
3231                      -- Multiply with the quantity ordered
3232                      -- 5/2/2002 mpande modified ordered qty is the line quantity
3233                     l_earned_amount            :=    l_earned_amount * (l_line_quantity);
3234                  END IF;
3235 
3236                   --nirprasa, ER 8399134 multi-currency enhancement
3237                   IF l_offer_transaction_curr IS NOT NULL AND l_offer_transaction_curr <> l_order_curr THEN
3238 
3239 
3240                      IF g_debug_flag = 'Y' THEN
3241                        ozf_utility_pvt.write_conc_log('l_order_curr: ' || l_order_curr);
3242                        ozf_utility_pvt.write_conc_log('l_offer_curr: ' || l_offer_curr);
3243                        ozf_utility_pvt.write_conc_log('l_earned_amount: ' || l_earned_amount);
3244                        ozf_utility_pvt.write_conc_log('l_order_org_id: ' || l_order_org_id);
3245                        ozf_utility_pvt.write_conc_log('**************************START****************************');
3246                        ozf_utility_pvt.write_conc_log(l_api_name||' From Amount l_earned_amount: '||l_earned_amount );
3247                        ozf_utility_pvt.write_conc_log(l_api_name||' From Curr l_order_curr: '||l_order_curr );
3248                        ozf_utility_pvt.write_conc_log(l_api_name||' l_exchange_rate_type: '|| l_exchange_rate_type);
3249                       END IF;
3250 
3251                      ozf_utility_pvt.convert_currency (x_return_status => x_return_status
3252                                                       ,p_from_currency => l_order_curr
3253                                                       ,p_to_currency   => l_offer_curr
3254                                                       ,p_conv_type     => l_exchange_rate_type -- Added for bug 7030415
3255                                                       ,p_from_amount   => l_earned_amount
3256                                                       ,x_to_amount     => l_conv_earned_amount
3257                                                       ,x_rate          => l_rate
3258                                                       );
3259 
3260                      IF g_debug_flag = 'Y' THEN
3261                         ozf_utility_pvt.write_conc_log(l_api_name||' To Curr l_offer_curr: '|| l_offer_curr );
3262                         ozf_utility_pvt.write_conc_log(l_api_name||' Converted Amount l_conv_earned_amount: '|| l_conv_earned_amount);
3263                         ozf_utility_pvt.write_conc_log('Earned amount is converted from order curr to offer curr');
3264                         ozf_utility_pvt.write_conc_log('***************************END******************************');
3265                         ozf_utility_pvt.write_conc_log('x_return_status: ' || x_return_status);
3266                      END IF;
3267 
3268                      IF x_return_status <> fnd_api.g_ret_sts_success THEN
3269                         GOTO l_endoflineadjloop;
3270                      END IF;
3271 
3272                      l_earned_amount := l_conv_earned_amount;
3273 
3274                      IF g_debug_flag = 'Y' THEN
3275                        ozf_utility_pvt.write_conc_log ('earned amt after currency conversion: ' || l_earned_amount);
3276                      END IF;
3277                   END IF;
3278 
3279               ELSIF l_operation = 'UPDATE' THEN
3280                  IF g_debug_flag = 'Y' THEN
3281                     ozf_utility_pvt.write_conc_log ('operation UPDATE');
3282                  END IF;
3283                   -- if the old and the new is the same we donot need to update it \
3284                  OPEN c_old_adjustment_amount (p_line_adj_tbl (i).price_adjustment_id);
3285                  FETCH c_old_adjustment_amount INTO l_old_adjusted_amount; -- in order curr
3286                  CLOSE c_old_adjustment_amount;
3287 
3288                  IF g_debug_flag = 'Y' THEN
3289                     ozf_utility_pvt.write_conc_log (
3290                      '    D: Old adjsutment amount '
3291                      || l_old_adjusted_amount
3292                      || '  Old price adjustment id '
3293                      || p_line_adj_tbl (i).price_adjustment_id
3294                      );
3295                  END IF;
3296                   -- if all the money coming in has been adjusted then set it to 0
3297                   --5/2/2002 the ordered quantity is the actual ordered quantity and not the difference
3298                  IF l_line_category_code = 'RETURN' THEN
3299                     IF g_debug_flag = 'Y' THEN
3300                        ozf_utility_pvt.write_conc_log ( '   LINE IS RETURN  ');
3301                     END IF;
3302                     l_line_quantity := -l_line_quantity; -- fred should be cancelled qutity.
3303                  END IF;
3304 
3305                  OPEN  c_offer_details(p_line_adj_tbl(i).list_header_id);
3306                  FETCH c_offer_details INTO  l_custom_setup_id, l_offer_name;
3307                  CLOSE c_offer_details;
3308 
3309                  IF g_debug_flag = 'Y' THEN
3310                         ozf_utility_pvt.write_conc_log(' l_custom_setup_id=' || l_custom_setup_id );
3311                  END IF;
3312 
3313 
3314                  IF  l_custom_setup_id = 118 THEN --ER9447673
3315                       MO_GLOBAL.set_policy_context('S', l_order_org_id);
3316                       l_column_name := FND_PROFILE.VALUE('OZF_ITEM_COST_COLUMN');
3317 
3318                       IF l_column_name IS NOT NULL AND l_column_name <> FND_API.G_MISS_CHAR THEN
3319                           l_stmt := 'SELECT ' || l_column_name ||' FROM oe_order_lines_all  WHERE line_id = :1 AND org_id = :2';
3320 
3321                           IF g_debug_flag = 'Y' THEN
3322                               ozf_utility_pvt.write_conc_log('Query to obtain purchase price '||l_stmt);
3323                           END IF;
3324 
3325                           OPEN c_purchase_price FOR l_stmt using p_line_adj_tbl(i).line_id, l_order_org_id;
3326                           FETCH c_purchase_price INTO l_cost_price;
3327                           CLOSE c_purchase_price;
3328                       END IF;
3329 
3330                      -- Catch Weight ER - start
3331                       IF g_debug_flag = 'Y' THEN
3332                      ozf_utility_pvt.write_conc_log('Order_quantity_uom=' || l_order_quantity_uom );
3333                      ozf_utility_pvt.write_conc_log('order_quantity=' || l_line_quantity );
3334 --                     ozf_utility_pvt.write_conc_log('shipping_quantity_uom=' || l_shipping_quantity_uom );
3335 --                     ozf_utility_pvt.write_conc_log('shipping_quantity=' || l_shipping_quantity );
3336                      -- Catch Weight ER - end
3337                        ozf_utility_pvt.write_conc_log(' l_cost_price' || l_cost_price );
3338                       END IF;
3339 
3340                       IF (l_cost_price = -1) THEN
3341                           IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_debug_low) THEN
3342                                  fnd_message.set_name('OZF', 'OZF_COST_PRICE_NOT_FOUND');
3343                                  FND_MESSAGE.Set_Token('OFFR',l_offer_name);
3344                                  FND_MESSAGE.Set_Token('ORDER',p_line_adj_tbl(i).header_id);
3345                                  FND_MESSAGE.Set_Token('ITEM',l_product_id);
3346                                  FND_MESSAGE.Set_Token('TEXT',sqlerrm);
3347                                  fnd_msg_pub.add;
3348                           END IF;
3349                              GOTO l_endoflineadjloop;
3350                       END IF;
3351 
3352                       IF g_debug_flag = 'Y' THEN
3353                           ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_cost_price = ' || l_cost_price);
3354                           ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_line_quantity = ' || l_line_quantity);
3355                           ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_arithmetic_operator = ' || l_arithmetic_operator);
3356                           ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ l_operand = ' || l_operand);
3357                       END IF;
3358               -- Catch Weight ER - start
3359               -- Converting shipping quantity from shipping uom to order uom only when arithmatic op is not AMT, as in case of AMT, operand takes care of catch weight
3360 	      IF l_arithmetic_operator <> 'AMT' THEN
3361 			/*OZF_UTILITY_PVT.get_catch_weight_quantity (
3362 			  p_inventory_item_id      =>   l_product_id,
3363 			  p_order_line_id	         =>   p_line_adj_tbl (i).line_id,
3364 			  x_return_status	         =>   l_return_status,
3365 			  x_cw_quantity		         =>   l_cw_quantity,
3366 			  x_cw_quantity_uom	       =>   l_cw_quantity_uom );*/
3367 
3368 		    -- getting fulfillment_base from OE API. In case of performance issue can think of using fulfillment_base from existing cursor
3369 		    l_fulfillment_base := OE_DUAL_UOM_UTIL.get_fulfillment_base(p_line_adj_tbl (i).line_id) ;
3370 
3371 		    IF l_fulfillment_base = 'S' THEN
3372 		       l_cw_quantity     := l_shipping_quantity;
3373 		       l_cw_quantity_uom := l_shipping_quantity_uom;
3374 		    ELSE
3375 		       l_cw_quantity     := NVL(l_shipping_quantity2, l_shipping_quantity);
3376 		       l_cw_quantity_uom := NVL(l_shipping_quantity_uom2, l_shipping_quantity_uom);
3377 		    END IF;
3378 
3379 		    -- Converting shipping quantity from shipping uom to order uom as cost price is as per order uom
3380 		      IF l_cw_quantity_uom IS NOT NULL AND l_cw_quantity_uom <> l_order_quantity_uom THEN
3381 			 l_line_quantity := inv_convert.inv_um_convert(
3382 						    l_product_id                             -- item_id
3383 						    ,NULL                                    -- precision
3384                       				    ,l_cw_quantity                           -- from_quantity
3385                       				    ,l_cw_quantity_uom                       -- from_unit
3386 						    ,l_order_quantity_uom                    -- to_unit
3387 						    ,NULL                                    -- from_name
3388 						    ,NULL                                    -- to_name
3389 						    );
3390 			 ozf_utility_pvt.write_conc_log(' Catch Weight   D: adjust_accrual()_ l_line_quantity = ' || l_line_quantity);
3391 		      END IF;
3392 		END IF;
3393 		-- Catch Weight ER - end
3394 
3395 --		      [Catch Weight Calculation:
3396 --		       Order Booked  : 3 Case = 36 Ea = 360 Pounds
3397 --		       Order Shipped : 300 Pounds = 2.5 Case
3398 --		       Cost Price : 300 per Case
3399 --
3400 --		       Ship & Debit Offer : Discount Type = 5% per Case
3401 --		       Accrual After booking order : 5(l_operand) * 300(l_cost_price) / 100 * 3 (l_line_quantity) = 45
3402 --		       Accrual Calculated Below    : 5(l_operand) * 300(l_cost_price) / 100 * 2.5 (converted l_line_quantity) = 37.5
3403 --		       Ship & Debit Offer : Discount Type = 5% per Pound
3404 --		       Accrual After booking order : 5(l_operand) * 300(l_cost_price) / 100 * 3 (l_line_quantity) = 45
3405 --		       Accrual Calculated Below    : 5(l_operand) * 300(l_cost_price) / 100 * 2.5 (converted l_line_quantity) = 37.5
3406 --
3407 --		       Ship & Debit Offer : Discount Type = 1 AMT per Pound -- no uom conversion required
3408 --		       Accrual After booking order : 3 (l_line_quantity) * 120 (l_operand) = 360
3409 --		       Accrual Calculated Below    : 3(l_line_quantity) * 100 (l_operand) = 300
3410 --		       Ship & Debit Offer : Discount Type = 1 AMT per Case -- no uom conversion required
3411 --		       Accrual After booking order : 3 (l_line_quantity) * 1 (l_operand) = 3
3412 --		       Accrual Calculated Below    : 3(l_line_quantity) * 0.833 (l_operand) = 2.5
3413 --		       Ship & Debit Offer : Discount Type = 2 NEWPRICE per Pounds
3414 --		       Accrual After booking order : (300(l_cost_price) - 240(l_operand)) * 3(l_line_quantity) = 180
3415 --		       Accrual Calculated Below    : (300(l_cost_price) - 240(l_operand)) * 2.5(converted l_line_quantity) = 150
3416 --		       Ship & Debit Offer : Discount Type = 250 NEWPRICE per Case
3417 --		       Accrual After booking order : (300(l_cost_price) - 250(l_operand)) * 3(l_line_quantity) = 150
3418 --		       Accrual Calculated Below    : (300(l_cost_price) - 250(l_operand)) * 2.5(converted l_line_quantity) = 125]
3419 
3420                       IF l_arithmetic_operator = '%' THEN
3421                           l_new_adjustment_amount := (NVL(l_operand, 0)) * l_cost_price / 100 * ( l_line_quantity);
3422                       ELSIF l_arithmetic_operator = 'NEWPRICE' THEN
3423                           l_new_adjustment_amount := (l_cost_price - (NVL(l_operand, 0))) * ( l_line_quantity);
3424                       ELSE
3425                                l_new_adjustment_amount    :=   (l_line_quantity ) * (NVL (l_operand, 0));
3426                       END IF;
3427                  ELSE
3428                        l_new_adjustment_amount    :=   (l_line_quantity ) * (-(NVL (l_new_adjustment_amount, 0)));
3429                  END IF;
3430                  --ER9447673
3431 
3432                 /* l_new_adjustment_amount    :=   (l_line_quantity )
3433                                              * (-(NVL (l_new_adjustment_amount, 0)));*/
3434 
3435                  IF g_debug_flag = 'Y' THEN
3436                     ozf_utility_pvt.write_conc_log('    D: adjust_accrual() l_new_adjustment_amount=' || l_new_adjustment_amount );
3437                  END IF;
3438 
3439                   --nirprasa, ER 8399134, multi-currency enhancement
3440                  IF l_offer_curr <> l_order_curr AND l_offer_transaction_curr IS NOT NULL THEN
3441 
3442                      IF g_debug_flag = 'Y' THEN
3443                      ozf_utility_pvt.write_conc_log('l_order_curr: ' || l_order_curr);
3444                      ozf_utility_pvt.write_conc_log('l_offer_curr: ' || l_offer_curr);
3445                      ozf_utility_pvt.write_conc_log('l_new_adjustment_amount: ' || l_new_adjustment_amount);
3446                      END IF;
3447 
3448                      ozf_utility_pvt.convert_currency (x_return_status => x_return_status
3449                                                       ,p_from_currency => l_order_curr
3450                                                       ,p_to_currency   => l_offer_curr
3451                                                       ,p_conv_type     => l_exchange_rate_type -- Added for bug 7030415
3452                                                       ,p_from_amount   => l_new_adjustment_amount
3453                                                       ,x_to_amount     => l_conv_adjustment_amount
3454                                                       ,x_rate          => l_rate
3455                                                       );
3456 
3457                      ozf_utility_pvt.write_conc_log('x_return_status: ' || x_return_status);
3458 
3459                      IF x_return_status <> fnd_api.g_ret_sts_success THEN
3460                         GOTO l_endoflineadjloop;
3461                      END IF;
3462 
3463                      l_new_adjustment_amount := l_conv_adjustment_amount;
3464 
3465                      IF g_debug_flag = 'Y' THEN
3466                         ozf_utility_pvt.write_conc_log ('new adjusted amt after currency conversion: ' || l_new_adjustment_amount);
3467                      END IF;
3468                   END IF;
3469 
3470                   IF g_debug_flag = 'Y' THEN
3471                         ozf_utility_pvt.write_conc_log ('Check for Partial Shipment: ' || p_line_adj_tbl (i).line_id);
3472                   END IF;
3473 
3474 
3475                  l_earned_amount            :=  l_new_adjustment_amount - NVL(l_old_adjusted_amount,0);
3476 
3477                  IF g_debug_flag = 'Y' THEN
3478                     ozf_utility_pvt.write_conc_log ('    D: Update earned amount '|| l_earned_amount);
3479                  END IF;
3480 
3481                 -- Changes by rimehrot (12/8/2004) for bug 3697213
3482                -- When order is re-priced and offer is removed from the order, a message with operation
3483                -- 'DELETE' is sent and the original accrual should be reverted in this case.
3484               ELSIF l_operation = 'DELETE' AND p_line_adj_tbl (i).price_adjustment_id IS NOT NULL THEN
3485                  IF g_debug_flag = 'Y' THEN
3486                    ozf_utility_pvt.write_conc_log ('operation DELETE');
3487                  END IF;
3488 
3489                  FOR old_adjustment_rec IN
3490                    c_old_adjustment_amt (p_line_adj_tbl (i).price_adjustment_id)
3491                  LOOP
3492                     l_adj_amount := -old_adjustment_rec.amount;
3493                     IF old_adjustment_rec.amount = 0 THEN
3494                        GOTO l_endofloop;
3495                     END IF;
3496 
3497                     l_util_rec :=NULL;
3498                     l_act_budgets_rec :=NULL;
3499                     l_util_rec.object_type := 'ORDER';
3500                     l_util_rec.object_id   := p_line_adj_tbl (i).header_id;
3501                     l_util_rec.product_id := old_adjustment_rec.product_id;
3502                     l_util_rec.price_adjustment_id := p_line_adj_tbl (i).price_adjustment_id;
3503                     ----Bug 13463758 populate order_line_id for DELETE flow
3504                     l_util_rec.order_line_id   := p_line_adj_tbl (i).line_id;
3505                     l_act_budgets_rec.budget_source_type := 'OFFR';
3506                     l_act_budgets_rec.budget_source_id := p_line_adj_tbl (i).list_header_id;
3507                     l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3508                     l_act_budgets_rec.act_budget_used_by_id := p_line_adj_tbl (i).list_header_id;
3509                     l_act_budgets_rec.parent_src_apprvd_amt := l_adj_amount;
3510                     l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
3511                     l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
3512                     l_act_budgets_rec.request_amount := -old_adjustment_rec.plan_curr_amount;
3513                     l_act_budgets_rec.request_currency := l_order_curr;
3514                     l_util_rec.amount := l_adj_amount ;
3515                     l_util_rec.plan_curr_amount :=  l_act_budgets_rec.request_amount;
3516                     l_util_rec.component_id := p_line_adj_tbl (i).list_header_id;
3517                     l_util_rec.currency_code :=old_adjustment_rec.currency_code;
3518                     l_util_rec.fund_id :=old_adjustment_rec.fund_id;
3519                     -- kpatro 11/09/2006 fix for bug 5523042
3520                     l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
3521                     l_util_rec.component_type := old_adjustment_rec.component_type;
3522 
3523                     --nirprasa, ER 8399134 multi-currency enhancement
3524                     l_util_rec.plan_currency_code := old_adjustment_rec.plan_currency_code;
3525                     l_util_rec.fund_request_currency_code := old_adjustment_rec.fund_request_currency_code;
3526                     l_util_rec.fund_request_amount := -old_adjustment_rec.fund_request_amount;
3527 
3528                   -- yzhao: 06/23/2004 if old record needs to post, set this gl flag to N, otherwise, no posting
3529                     IF old_adjustment_rec.gl_posted_flag IN (G_GL_FLAG_NULL, G_GL_FLAG_NOLIAB) THEN
3530                        l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;  -- 'N';
3531                     ELSE
3532                        l_util_rec.gl_posted_flag := G_GL_FLAG_NO;  -- 'N';
3533                     END IF;
3534                   -- rimehrot: initially put the gl_posted_flag as N. If post_accrual_to_gl call reqd later,
3535                   -- will get changed accordingly depending on the value obtained after posting.
3536 
3537                     create_fund_utilization (
3538                        p_act_util_rec=> l_util_rec,
3539                      p_act_budgets_rec=> l_act_budgets_rec,
3540                      x_utilization_id => l_utilization_id,
3541                      x_return_status=> l_return_status,
3542                      x_msg_count=> x_msg_count,
3543                      x_msg_data=> x_msg_data
3544                      );
3545 
3546                     IF g_debug_flag = 'Y' THEN
3547                        ozf_utility_pvt.write_conc_log (
3548                         'create utlization from cancelled order returns '|| l_return_status
3549                        );
3550                     END IF;
3551 
3552                     IF l_return_status <> fnd_api.g_ret_sts_success THEN
3553                        GOTO l_endoflineadjloop;
3554                     END IF;
3555 
3556                   -- If gl_posted_flag of original accrual has been posted, call post_accrual_to_gl
3557                   -- to post new accrual
3558 
3559                     IF old_adjustment_rec.gl_posted_flag IN (G_GL_FLAG_YES, G_GL_FLAG_FAIL) THEN
3560                     -- get details of utilization created above.
3561                     -- fred could be removed. direct to use from above cursor.
3562                        OPEN c_get_util_rec (l_utilization_id);
3563                        FETCH c_get_util_rec INTO l_object_version_number, l_plan_type, l_utilization_type, l_amount,
3564                           l_fund_id, l_acctd_amount, l_plan_id, l_plan_amount;
3565                        CLOSE c_get_util_rec;
3566 
3567                        post_accrual_to_gl( p_util_utilization_id            => l_utilization_id
3568                                      , p_util_object_version_number      => l_object_version_number
3569                                      , p_util_amount                     => l_amount
3570                                      , p_util_plan_type                  => l_plan_type
3571                                      , p_util_plan_id                    => l_plan_id
3572                                      , p_util_plan_amount                => l_plan_amount
3573                                      , p_util_utilization_type           => l_utilization_type
3574                                      , p_util_fund_id                    => l_fund_id
3575                                      , p_util_acctd_amount               => l_acctd_amount
3576                                      , x_gl_posted_flag                  => l_gl_posted_flag
3577                                      , x_return_status                   => l_return_status
3578                                      , x_msg_count                       => x_msg_count
3579                                      , x_msg_data                        => x_msg_data
3580                                      );
3581 
3582                    -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
3583                        IF g_debug_flag = 'Y' THEN
3584                           ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() processing price adjustment id' || p_line_adj_tbl (i).line_id
3585                           || '  post_accrual_to_gl(util_id=' || l_utilization_id ||
3586                            ' gl_posted_flag' || l_gl_posted_flag || ') returns ' || l_return_status);
3587                        END IF;
3588                     END IF; -- end of gl_posted_flag in (Y, F)
3589 
3590                     <<l_endofloop>>
3591                     NULL;
3592                  END LOOP old_adjustment_rec;
3593                END IF; -- end if for mode
3594 
3595                --6373391
3596                IF g_debug_flag = 'Y' THEN
3597                ozf_utility_pvt.write_conc_log('NP line_id '||p_line_adj_tbl (i).line_id);
3598                END IF;
3599 
3600                OPEN c_split_line(p_line_adj_tbl (i).line_id);
3601                FETCH c_split_line INTO l_new_line_id;
3602                CLOSE c_split_line;
3603 
3604                IF g_debug_flag = 'Y' THEN
3605                ozf_utility_pvt.write_conc_log('NP  l_new_line_id '||l_new_line_id);
3606                END IF;
3607 
3608                -- OM sometimes is not sending create message for new split line . So handle it in TM.
3609                -- and create accrual so that we get a rec in utilization table for split line
3610 
3611                IF  NVL(l_earned_amount,0) = 0 AND p_line_adj_tbl (i).operation <> 'CREATE'
3612                AND NVL(l_new_line_id,0) = 0 THEN
3613                   IF g_debug_flag = 'Y' THEN
3614                      ozf_utility_pvt.write_conc_log('    D: adjust_accrual()  earned amount = 0. No adjustment');
3615                   END IF;
3616                   GOTO l_endoflineadjloop;
3617                END IF;
3618 
3619                IF g_debug_flag = 'Y' THEN
3620                   ozf_utility_pvt.write_conc_log(' creating adjustment for '||l_new_line_id);
3621                   ozf_utility_pvt.write_conc_log('    D: adjust_accrual()  earned amount = ' || l_earned_amount);
3622                END IF;
3623 
3624                l_count := l_count + 1;
3625                l_adj_amt_tbl (l_count).order_header_id := p_line_adj_tbl (i).header_id;
3626                l_adj_amt_tbl (l_count).order_line_id := p_line_adj_tbl (i).line_id;
3627                l_adj_amt_tbl (l_count).price_adjustment_id := p_line_adj_tbl (i).price_adjustment_id;
3628                l_adj_amt_tbl (l_count).qp_list_header_id:= p_line_adj_tbl (i).list_header_id;
3629                l_adj_amt_tbl (l_count).product_id := l_product_id;
3630                --l_adj_amt_tbl (l_count).earned_amount := ozf_utility_pvt.currround (l_earned_amount, l_order_curr);
3631                l_adj_amt_tbl (l_count).earned_amount := l_earned_amount;
3632                l_adj_amt_tbl (l_count).offer_currency:= l_offer_curr;
3633                --nirprasa, ER 8399134 multi-currency enhancement, added parameter order currency.
3634                --l_adj_amt_tbl, will be passed on to post_accrual_to_budget
3635                l_adj_amt_tbl (l_count).order_currency:= l_order_curr;
3636                l_adj_amt_tbl (l_count).cost_price:= l_cost_price;
3637                l_adj_amt_tbl (l_count).cost_price_currency_code:= l_order_curr;
3638             END IF;
3639             <<l_endoflineadjloop>>
3640 
3641             IF x_return_status <> fnd_api.g_ret_sts_success THEN
3642                IF g_debug_flag = 'Y' THEN
3643                   ozf_utility_pvt.write_conc_log (
3644                     '   /****** Adjustment Failure *******/ Offer Id: "'|| p_line_adj_tbl(i).list_header_id ||'"' || 'Price Adjustment Id'||p_line_adj_tbl (i).price_adjustment_id);
3645                END IF;
3646                   -- Initialize the Message list for Next Processing
3647                ROLLBACK TO line_adjustment;
3648                x_return_status := fnd_api.g_ret_sts_error ;
3649                EXIT;
3650             ELSE
3651                IF g_debug_flag = 'Y' THEN
3652                   ozf_utility_pvt.write_conc_log(
3653                     '   /****** Adjustment Success *******/ Offer Id: "'|| p_line_adj_tbl(i).list_header_id ||
3654                     '"' || ' Price Adjustment Id "'||p_line_adj_tbl (i).price_Adjustment_id ||'"' );
3655                END IF;
3656             END IF;
3657 
3658          END LOOP new_line_tbl_loop;
3659 
3660          IF l_adj_amt_tbl.count > 0 THEN
3661             post_accrual_to_budget (
3662                    p_adj_amt_tbl         => l_adj_amt_tbl
3663                  , x_return_status       => l_return_status
3664                  , x_msg_count           => x_msg_count
3665                  , x_msg_data            => x_msg_data
3666             );
3667          END IF;
3668 
3669          IF g_debug_flag = 'Y' THEN
3670             ozf_utility_pvt.write_conc_log('    D: post_accrual_to_budget returns ' || l_return_status);
3671          END IF;
3672          x_return_status  := l_return_status;
3673          fnd_msg_pub.count_and_get (
3674             p_count=> x_msg_count,
3675             p_data=> x_msg_data,
3676             p_encoded=> fnd_api.g_false
3677          );
3678 
3679    EXCEPTION
3680       --nepanda : Added exception block for normal errors and unexpected errors, before checking for OTHERS
3681       WHEN fnd_api.g_exc_error THEN
3682          x_return_status            := fnd_api.g_ret_sts_error;
3683         fnd_msg_pub.count_and_get (
3684             p_count=> x_msg_count,
3685             p_data=> x_msg_data,
3686             p_encoded=> fnd_api.g_false
3687          );
3688       WHEN fnd_api.g_exc_unexpected_error THEN
3689          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3690 
3691          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3692             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
3693          END IF;
3694          ozf_utility_pvt.write_conc_log(' /**************UNEXPECTED EXCEPTION in adjust_accrual *************/');
3695         fnd_msg_pub.count_and_get (
3696             p_count=> x_msg_count,
3697             p_data=> x_msg_data,
3698             p_encoded=> fnd_api.g_false
3699          );
3700       WHEN OTHERS THEN
3701          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3702 
3703         ozf_utility_pvt.write_conc_log(' /**************UNEXPECTED EXCEPTION in adjust_accrual *************/');
3704          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3705             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
3706          END IF;
3707 
3708          fnd_msg_pub.count_and_get (
3709             p_count=> x_msg_count,
3710             p_data=> x_msg_data,
3711             p_encoded=> fnd_api.g_false
3712          );
3713    END adjust_accrual;
3714    ------------------------------------------------------------------------------
3715 -- Procedure Name
3716 --   recalculate_earnings
3717 -- Purpose
3718 --   This procedure re-converts the converted amounts in utilization table
3719 --   gl_date will be used as exchange_date.
3720 -- History
3721 -- 04/29/2009 nirprasa Created
3722 ------------------------------------------------------------------------------
3723 
3724   PROCEDURE recalculate_earnings (
3725       p_exchange_rate_date          IN            DATE,
3726       p_exchange_rate_type          IN            VARCHAR2,
3727       p_util_org_id                 IN            NUMBER,
3728       p_currency_code               IN            VARCHAR2,
3729       p_plan_currency_code          IN            VARCHAR2,
3730       p_fund_req_currency_code      IN            VARCHAR2,
3731       p_amount                      IN            NUMBER,
3732       p_plan_curr_amount            IN            NUMBER,
3733       p_plan_curr_amount_rem        IN            NUMBER,
3734       p_univ_curr_amount            IN            NUMBER,
3735       p_acctd_amount                IN            NUMBER,
3736       p_fund_req_amount             IN            NUMBER,
3737       p_util_plan_id                IN            NUMBER,
3738       p_util_plan_type              IN            VARCHAR2,
3739       p_util_fund_id                IN            NUMBER,
3740       p_util_utilization_id         IN            NUMBER,
3741       p_util_utilization_type       IN            VARCHAR2,
3742       x_return_status               OUT NOCOPY    VARCHAR2,
3743       x_msg_count                   OUT NOCOPY    VARCHAR2,
3744       x_msg_data                    OUT NOCOPY    VARCHAR2);
3745 
3746 ------------------------------------------------------------------------------
3747 -- Procedure Name
3748 --   adjust_changed_order
3749 -- Purpose
3750 --   This procedure will calculate and update the accrual info for cancelled order
3751 --     and post to gl for shipped order.
3752 --
3753 --  created      mpande     02/15/2002
3754 --  modified     yzhao      03/19/2003   added posting to GL for shipped order lines
3755 ------------------------------------------------------------------------------
3756    PROCEDURE adjust_changed_order (
3757       p_api_version        IN       NUMBER,
3758       p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false,
3759       p_commit             IN       VARCHAR2 := fnd_api.g_false,
3760       p_validation_level   IN       NUMBER := fnd_api.g_valid_level_full,
3761       x_return_status      OUT NOCOPY      VARCHAR2,
3762       x_msg_count          OUT NOCOPY      NUMBER,
3763       x_msg_data           OUT NOCOPY      VARCHAR2,
3764       p_header_rec         IN       oe_order_pub.header_rec_type,
3765       p_old_header_rec     IN       oe_order_pub.header_rec_type,
3766       p_line_tbl           IN       oe_order_pub.line_tbl_type,
3767       p_old_line_tbl       IN       oe_order_pub.line_tbl_type
3768    ) IS
3769       l_return_status           VARCHAR2 (1)                          ;
3770       l_api_name       CONSTANT VARCHAR2 (30)                           := 'Adjust_Changed_order';
3771       l_api_version    CONSTANT NUMBER                                  := 1.0;
3772       --  local variables
3773       l_qp_list_hdr_id          NUMBER;
3774       l_earned_amount           NUMBER;
3775       l_old_earned_amount       NUMBER;
3776       l_header_id               NUMBER; -- order or invoice id
3777       l_line_id                 NUMBER; -- order or invoice id
3778       l_util_rec                ozf_fund_utilized_pvt.utilization_rec_type;
3779       l_empty_util_rec          ozf_fund_utilized_pvt.utilization_rec_type;
3780       l_util_id                 NUMBER;
3781       l_util_curr               VARCHAR2 (30);
3782       l_adj_amount              NUMBER;
3783       l_converted_adj_amount    NUMBER;
3784       l_order_status            VARCHAR2 (30);
3785       l_order_booked_flag       VARCHAR2 (1);
3786       l_line_quantity           NUMBER;
3787       l_old_adjusted_amount     NUMBER                                  := 0;
3788       l_order_curr              VARCHAR2 (150);
3789       l_cancelled_quantity      NUMBER;
3790       l_modifier_level_code     VARCHAR2 (30);
3791       l_line_status             VARCHAR2 (30);
3792       l_new_adjustment_amount   NUMBER;
3793       l_act_budgets_rec         ozf_actbudgets_pvt.act_budgets_rec_type;
3794       l_empty_act_budgets_rec   ozf_actbudgets_pvt.act_budgets_rec_type;
3795       l_order_number            NUMBER;
3796       l_gl_posted_flag          VARCHAR2 (1);
3797       l_orig_adj_amount         NUMBER;
3798       l_rate                    NUMBER;
3799       l_total                   NUMBER;
3800       l_gl_date                 DATE;
3801       l_new_line_id             NUMBER;
3802       l_new_adj_id              NUMBER;
3803       l_sales_transaction_rec   OZF_SALES_TRANSACTIONS_PVT.SALES_TRANSACTION_REC_TYPE;
3804       l_sales_transaction_id    NUMBER;
3805       l_org_id                  NUMBER;
3806       l_sales_trans             NUMBER;
3807       l_utilization_id          NUMBER;
3808 
3809       l_utilIdTbl               utilIdTbl;
3810       l_objVerTbl               objVerTbl;
3811       l_amountTbl               amountTbl;
3812       l_planTypeTbl             planTypeTbl;
3813       l_planIdTbl               planIdTbl;
3814       l_planAmtTbl              planAmtTbl;
3815       l_utilTypeTbl             utilTypeTbl;
3816       l_fundIdTbl               fundIdTbl;
3817       l_acctAmtTbl              acctAmtTbl;
3818       l_orgIdTbl                orgIdTbl;
3819 
3820       l_excDateTbl              excDateTbl;
3821       l_excTypeTbl              excTypeTbl;
3822       l_currCodeTbl             currCodeTbl;
3823       l_planCurrCodeTbl         planCurrCodeTbl;
3824       l_fundReqCurrCodeTbl      fundReqCurrCodeTbl;
3825       l_planCurrAmtTbl          planCurrAmtTbl;
3826       l_planCurrAmtRemTbl       planCurrAmtRemTbl;
3827       l_univCurrAmtTbl          univCurrAmtTbl;
3828       CURSOR party_id_csr(p_cust_account_id NUMBER) IS
3829          SELECT party_id
3830          FROM hz_cust_accounts
3831          WHERE cust_account_id = p_cust_account_id;
3832 
3833       CURSOR party_site_id_csr(p_account_site_id NUMBER) IS
3834          SELECT a.party_site_id
3835          FROM hz_cust_acct_sites_all a,
3836               hz_cust_site_uses_all b
3837          WHERE b.site_use_id = p_account_site_id
3838          AND   b.cust_acct_site_id = a.cust_acct_site_id;
3839 
3840       CURSOR sales_transation_csr(p_line_id NUMBER) IS
3841          SELECT 1 FROM DUAL WHERE EXISTS
3842          ( SELECT 1
3843            FROM ozf_sales_transactions_all trx
3844            WHERE trx.line_id = p_line_id
3845            AND source_code = 'OM');
3846 
3847       CURSOR c_order_info (p_header_id IN NUMBER) IS
3848          SELECT flow_status_code,
3849                 booked_flag,
3850                 transactional_curr_code,
3851                 order_number,
3852                 org_id
3853          FROM oe_order_headers_all
3854          WHERE header_id = p_header_id;
3855 
3856       CURSOR c_all_price_adjustments (p_line_id IN NUMBER) IS
3857          SELECT price_adjustment_id,
3858                 list_header_id,
3859                 adjusted_amount,          -- yzhao: 03/21/2003 added following 2 for shipped order
3860                 header_id,
3861                 operand,
3862                 arithmetic_operator
3863          FROM oe_price_adjustments
3864          WHERE line_id = p_line_id;
3865 
3866       -- used for cancelled order and partial ship.
3867       CURSOR c_old_adjustment_amount (p_price_adjustment_id IN NUMBER) IS
3868          SELECT sum(plan_curr_amount) plan_curr_amount, sum(amount) amount,
3869                 sum(fund_request_amount) fund_request_amount, ----nirprasa, ER 8399134
3870                    fund_id,currency_code,
3871                    'N' gl_posted_flag,min(plan_id) plan_id,
3872                    utilization_type,adjustment_type,
3873                    price_adjustment_id,orig_utilization_id,
3874                    exchange_rate_type, --nirprasa, added for LGE enhancement
3875                    plan_currency_code, ----nirprasa, ER 8399134
3876                    fund_request_currency_code ----nirprasa, ER 8399134
3877         FROM ozf_funds_utilized_all_b
3878         WHERE price_adjustment_id = p_price_adjustment_id
3879         AND object_type = 'ORDER'
3880         AND NVL(gl_posted_flag,'N') <> 'Y'
3881         GROUP BY fund_id,
3882                  currency_code,
3883                  gl_posted_flag,
3884                  utilization_type,
3885                  adjustment_type,
3886                  price_adjustment_id,
3887                  orig_utilization_id,
3888                  exchange_rate_type,
3889                  plan_currency_code,
3890                  fund_request_currency_code;
3891 
3892       -- yzhao: 03/21/2003 get old adjustment amount per price_adjustment_id, copy from adjust_accrual
3893       CURSOR c_old_adjustment_total_amount (p_price_adjustment_id IN NUMBER) IS
3894          SELECT SUM (plan_curr_amount)  -- change to plan_curr_amount from acct_amount by feliu
3895          FROM ozf_funds_utilized_all_b
3896          WHERE price_adjustment_id = p_price_adjustment_id
3897          AND object_type = 'ORDER'
3898          AND utilization_type NOT IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT'); -- remove adjustment amount on 08/03/04 by feliu
3899 
3900      -- yzhao: 03/21/2003 get shipped/invoiced order's accraul record, post to GL
3901      -- changed for bug 6140826
3902      --nirprasa, ER 8399134 query fund_request_amount
3903      CURSOR c_get_accrual_rec(p_line_id IN NUMBER) IS
3904         SELECT utilization_id, object_version_number, plan_type, utilization_type, amount
3905              , fund_id, acctd_amount, fund_request_amount, plan_id,org_id
3906              , exchange_rate_type, exchange_rate_date
3907              , currency_code, plan_currency_code, fund_request_currency_code
3908              , plan_curr_amount, plan_curr_amount_remaining
3909              , univ_curr_amount
3910         FROM   ozf_funds_utilized_all_b
3911         WHERE  price_adjustment_id IN (SELECT price_adjustment_id
3912                                       FROM   oe_price_adjustments
3913                                       WHERE  line_id = p_line_id)
3914         AND    gl_posted_flag = G_GL_FLAG_NO  -- 'N'
3915         AND object_type = 'ORDER'
3916        -- 05/11/2004  kdass  fixed bug 3609771 - added UTILIZED to query
3917         AND    utilization_type in ('ACCRUAL', 'LEAD_ACCRUAL','SALES_ACCRUAL')
3918         UNION ALL -- added for bug 5485334 kpatro
3919         select utilization_id, object_version_number, plan_type, utilization_type, amount
3920              , fund_id, acctd_amount, plan_curr_amount, plan_id,org_id
3921              , exchange_rate_type, exchange_rate_date
3922              , currency_code, plan_currency_code, fund_request_currency_code
3923              , plan_curr_amount, plan_curr_amount_remaining
3924              , univ_curr_amount
3925               from  ozf_funds_utilized_all_b
3926         where object_type = 'ORDER'
3927         and order_line_id = p_line_id
3928         AND  gl_posted_flag = G_GL_FLAG_NO
3929         AND utilization_type IN ('ADJUSTMENT','LEAD_ADJUSTMENT')
3930            AND (price_adjustment_id IS NULL or (price_adjustment_id =-1 and orig_utilization_id<>-1)); --added for bug 6021635 nirprasa
3931 
3932 
3933      CURSOR c_actual_shipment_date(p_line_id IN NUMBER) IS
3934         SELECT actual_shipment_date, shipping_quantity, shipping_quantity_uom, shipping_quantity2, shipping_quantity_uom2, fulfillment_base
3935         FROM oe_order_lines_all
3936         WHERE line_id = p_line_id;
3937 
3938      --fix for bug 13824967
3939      CURSOR c_invoice_date(p_line_id IN NUMBER, p_order_number IN VARCHAR2) IS
3940         SELECT  cust.trx_date     -- transaction(invoice) date
3941         FROM ra_customer_trx_all cust
3942            , ra_customer_trx_lines_all cust_lines
3943         WHERE cust.customer_trx_id = cust_lines.customer_trx_id
3944         AND cust_lines.interface_line_attribute1 = p_order_number -- added condition for partial index for bug fix 3917556
3945         AND cust_lines.interface_line_attribute6 = TO_CHAR(p_line_id)
3946         AND cust_lines.interface_line_context = 'ORDER ENTRY';
3947 
3948      -- add by feliu on 08/03/04, get split line id to use in create postivie adjustment.
3949      CURSOR c_split_line(p_line_id IN NUMBER, p_header_id IN NUMBER) IS
3950         SELECT line_id
3951         FROM oe_order_lines_all
3952         WHERE header_id = p_header_id
3953         AND split_from_line_id = p_line_id
3954         AND split_by = 'SYSTEM';
3955 
3956      -- add by feliu on 08/03/04, get price_adjustment_id to use in create postivie adjustment.
3957      CURSOR c_new_adj_line(p_line_id IN NUMBER, p_header_id IN NUMBER) IS
3958         SELECT price_adjustment_id
3959         FROM  oe_price_adjustments
3960         WHERE line_id = p_line_id
3961         AND   list_header_id = p_header_id;
3962      -- add by feliu on 08/03/04, get max utilization id to use in create  adjustment.
3963      CURSOR c_max_utilized_id(p_price_adj_id IN NUMBER) IS
3964         SELECT max(utilization_id)
3965         FROM ozf_funds_utilized_all_b
3966         WHERE price_adjustment_id = p_price_adj_id
3967         AND object_type = 'ORDER';
3968 
3969       CURSOR c_orig_order_info (p_line_id IN NUMBER) IS
3970          SELECT NVL(shipped_quantity,ordered_quantity)
3971          FROM oe_order_lines_all
3972          WHERE line_id =p_line_id;
3973 
3974       CURSOR c_orig_adjustment_amount (p_order_line_id IN NUMBER) IS
3975          SELECT    plan_curr_amount, amount, fund_request_amount, --nirprasa, ER 8399134
3976                    fund_id,currency_code,
3977                    gl_posted_flag,plan_id,
3978                    utilization_type,price_adjustment_id,
3979                    adjustment_type,orig_utilization_id,
3980                    plan_currency_code,fund_request_currency_code --nirprasa, ER 8399134
3981         FROM ozf_funds_utilized_all_b
3982         WHERE order_line_id = p_order_line_id
3983         AND adjustment_type_id IN(-4,-5);
3984 
3985       --kdass bug 5953774
3986       CURSOR c_offer_currency (p_list_header_id IN NUMBER) IS
3987              SELECT nvl(transaction_currency_code, fund_request_curr_code) offer_currency,
3988              transaction_currency_code
3989            FROM ozf_offers
3990            WHERE qp_list_header_id = p_list_header_id;
3991 
3992 
3993 
3994         --added for bug
3995                 CURSOR c_old_adj_total_amount (p_order_line_id IN NUMBER) IS
3996          SELECT SUM (plan_curr_amount)  -- change to plan_curr_amount from acct_amount by feliu
3997          FROM ozf_funds_utilized_all_b
3998          WHERE price_adjustment_id = -1
3999          and order_line_id=p_order_line_id
4000          AND object_type = 'ORDER'
4001          AND utilization_type  IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT'); --
4002 
4003            CURSOR c_old_adjustment_details (p_order_line_id IN NUMBER) IS
4004           SELECT    plan_curr_amount, amount,
4005                    fund_id,currency_code,
4006                    gl_posted_flag,plan_id,
4007                    utilization_type,price_adjustment_id,
4008                    adjustment_type,orig_utilization_id
4009          FROM ozf_funds_utilized_all_b
4010          WHERE price_adjustment_id = -1
4011           and order_line_id=p_order_line_id
4012          AND object_type = 'ORDER'
4013          AND utilization_id=(
4014         SELECT max(utilization_id)
4015         FROM ozf_funds_utilized_all_b
4016         WHERE price_adjustment_id = -1
4017             and order_line_id=p_order_line_id
4018         AND object_type = 'ORDER');
4019 
4020 
4021          CURSOR  c_split_order_line_info(p_order_line_id IN NUMBER)  IS
4022         SELECT DECODE(line.line_category_code,'ORDER',line.ordered_quantity,
4023                                                                             'RETURN', -line.ordered_quantity) ordered_quantity,
4024              DECODE(line.line_category_code,'ORDER',NVL(line.shipped_quantity,0),
4025                                                                             'RETURN', line.invoiced_quantity,
4026                                                                             line.ordered_quantity) shipped_quantity
4027 
4028         FROM oe_order_lines_all line, oe_order_headers_all header
4029         WHERE line.line_id = p_order_line_id
4030         AND line.header_id = header.header_id;
4031 
4032 
4033          CURSOR c_all_fund_utilizations (p_line_id IN NUMBER) IS
4034         SELECT price_adjustment_id , plan_id
4035          FROM ozf_funds_utilized_all_b
4036          WHERE order_line_id = p_line_id;
4037 
4038          CURSOR c_offer_details (p_qp_list_header_id IN NUMBER) IS
4039          SELECT custom_setup_id
4040          FROM   ozf_offers
4041          WHERE  qp_list_header_id = p_qp_list_header_id;
4042 
4043           CURSOR c_discount_header(p_discount_line_id IN NUMBER) IS
4044          SELECT discount_type,volume_type
4045           FROM ozf_offer_discount_lines
4046           WHERE offer_discount_line_id = p_discount_line_id
4047           AND tier_type = 'PBH';
4048 
4049      CURSOR c_get_group(p_order_line_id IN NUMBER,p_list_header_id IN NUMBER) IS
4050        SELECT group_no,pbh_line_id,include_volume_flag
4051         FROM ozf_order_group_prod
4052         WHERE order_line_id = p_order_line_id
4053         AND qp_list_header_id = p_list_header_id;
4054 
4055      CURSOR c_market_option(p_list_header_id IN NUMBER, p_group_id IN NUMBER) IS
4056        SELECT opt.retroactive_flag
4057         FROM ozf_offr_market_options opt
4058         WHERE opt.GROUP_NUMBER= p_group_id
4059         AND opt.qp_list_header_id = p_list_header_id;
4060 
4061            CURSOR c_current_discount(p_volume IN NUMBER, p_parent_discount_id IN NUMBER) IS
4062          SELECT discount
4063         FROM ozf_offer_discount_lines
4064         WHERE p_volume > volume_from
4065              AND p_volume <= volume_to
4066          AND parent_discount_line_id = p_parent_discount_id;
4067 
4068           CURSOR  c_get_tier_limits (p_parent_discount_id IN NUMBER) IS
4069        SELECT MIN(volume_from),MAX(volume_to)
4070        FROM ozf_offer_discount_lines
4071        WHERE parent_discount_line_id = p_parent_discount_id;
4072 
4073      CURSOR  c_get_max_tier (p_max_volume_to IN NUMBER,p_parent_discount_id IN NUMBER)    IS
4074         SELECT  discount
4075         FROM ozf_offer_discount_lines
4076         WHERE volume_to =p_max_volume_to
4077         AND parent_discount_line_id = p_parent_discount_id;
4078 
4079    CURSOR c_discount(p_order_line_id  IN NUMBER) IS
4080        SELECT SUM(adjusted_amount_per_pqty)
4081        FROM oe_price_adjustments
4082        WHERE line_id = p_order_line_id
4083        AND accrual_flag = 'N'
4084        AND applied_flag = 'Y'
4085       -- AND list_line_type_code IN ('DIS', 'SUR', 'PBH', 'FREIGHT_CHARGE');
4086        AND list_line_type_code IN ('DIS', 'SUR', 'PBH');
4087         --
4088    CURSOR c_get_exchange_rate_info(p_utilization_id  IN NUMBER) IS
4089        SELECT exchange_rate_date,exchange_rate_type
4090        FROM ozf_funds_utilized_all_b
4091        WHERE utilization_id = p_utilization_id;
4092 
4093       l_shipped_qty   NUMBER;
4094       l_offer_curr    VARCHAR2(150);
4095       l_transaction_curr_code VARCHAR2(150);
4096       l_offer_amount  NUMBER;
4097 
4098       l_ordered_qty   NUMBER;
4099       l_offer_type    VARCHAR2(240);
4100 
4101        l_group_id                NUMBER;
4102       l_pbh_line_id             NUMBER;
4103       l_included_vol_flag       VARCHAR2(1);
4104       l_retroactive             VARCHAR2(1) ;
4105       l_discount_type           VARCHAR2(30);
4106       l_volume_type             VARCHAR2(30);
4107 
4108       l_msg_count               NUMBER;
4109       l_msg_data                VARCHAR2 (2000)        := NULL;
4110       l_source_code             VARCHAR2(30);
4111       l_volume                  NUMBER;
4112       l_new_discount            NUMBER;
4113       l_min_tier                NUMBER;
4114       l_max_tier                NUMBER;
4115       l_utilization_amount      NUMBER;
4116       l_unit_selling_price      NUMBER;
4117       l_unit_discount           NUMBER;
4118       l_exchange_rate_date      DATE;
4119       l_exchange_rate_type      VARCHAR2(30) := FND_API.G_MISS_CHAR;
4120 
4121       l_adjusted_amount         NUMBER;
4122       c_purchase_price          purchase_price_cursor_type;
4123       l_column_name             VARCHAR2(15);
4124       l_cost_price              NUMBER;
4125       l_custom_setup_id         NUMBER;
4126       l_stmt                    VARCHAR2(3000);
4127       l_operand                 NUMBER;
4128       l_arithmetic_operator     VARCHAR2(30);
4129 
4130       -- Catch Weight
4131       l_cw_quantity		NUMBER;
4132       l_cw_quantity_uom		VARCHAR2(10);
4133       l_shipping_quantity	NUMBER;
4134       l_shipping_quantity_uom	VARCHAR2(10);
4135       l_shipping_quantity2	NUMBER;
4136       l_shipping_quantity_uom2  VARCHAR2(10);
4137       l_fulfillment_base	VARCHAR2(1); -- Fix for Bug 16434010
4138 
4139    BEGIN
4140       SAVEPOINT adjust_changed_order;
4141       -- Standard call to check for call compatibility.
4142       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
4143          RAISE fnd_api.g_exc_unexpected_error;
4144       END IF;
4145       -- Initialize message list IF p_init_msg_list is set to TRUE.
4146       IF fnd_api.to_boolean (p_init_msg_list) THEN
4147          fnd_msg_pub.initialize;
4148       END IF;
4149       --  Initialize API return status to success
4150       x_return_status            := fnd_api.g_ret_sts_success;
4151       <<new_line_tbl_loop>>
4152 
4153       IF g_debug_flag = 'Y' THEN
4154          ozf_utility_pvt.write_conc_log (
4155             ' /*************************** DEBUG MESSAGE START for adjust_changed_line *************************/');
4156       END IF;
4157 
4158       FOR i IN NVL (p_line_tbl.FIRST, 1) .. NVL (p_line_tbl.LAST, 0)
4159       LOOP
4160          savepoint line_adjustment;
4161          IF g_debug_flag = 'Y' THEN
4162             ozf_utility_pvt.write_conc_log (
4163             '    D: Begin Processing For Order Line '|| p_line_tbl(i).line_id || ' cancelled_flag=' || p_line_tbl (i).cancelled_flag
4164                );
4165          END IF;
4166 
4167          IF g_debug_flag = 'Y' THEN
4168             ozf_utility_pvt.write_conc_log ('    D: AQ info for order header_id=' || p_line_tbl(i).header_id
4169                           -- || ' p_line_tbl(i).operation=' || p_line_tbl(i).operation
4170                            || ' p_line_tbl(i).flow_status_code=' || p_line_tbl(i).flow_status_code
4171                            || ' p_line_tbl(i).line_id=' || p_line_tbl(i).line_id
4172                            || ' p_line_tbl(i).ordered_quantity=' || p_line_tbl(i).ordered_quantity
4173                            || ' p_line_tbl(i).shipped_quantity=' || p_line_tbl(i).shipped_quantity
4174                            || ' p_line_tbl(i).invoiced_quantity=' || p_line_tbl(i).invoiced_quantity
4175                            || ' p_line_tbl(i).invoice_interface_status_code=' || p_line_tbl(i).invoice_interface_status_code
4176                            || ' p_line_tbl(i).line_category_code=' || p_line_tbl(i).line_category_code );
4177             ozf_utility_pvt.write_conc_log ('    D: AQ info for old order header_id=' || p_line_tbl(i).header_id
4178                           -- || ' p_line_tbl(i).operation=' || p_line_tbl(i).operation
4179                            || ' p_old_line_tbl(i).flow_status_code=' || p_old_line_tbl(i).flow_status_code
4180                            || ' p_old_line_tbl(i).line_id=' || p_old_line_tbl(i).line_id
4181                            || ' p_old_line_tbl(i).ordered_quantity=' || p_old_line_tbl(i).ordered_quantity
4182                            || ' p_old_line_tbl(i).shipped_quantity=' || p_old_line_tbl(i).shipped_quantity
4183                            || ' p_old_line_tbl(i).invoiced_quantity=' || p_old_line_tbl(i).invoiced_quantity
4184                            || ' p_old_line_tbl(i).invoice_interface_status_code=' || p_old_line_tbl(i).invoice_interface_status_code
4185                            || ' p_old_line_tbl(i).line_category_code=' || p_old_line_tbl(i).line_category_code );
4186          END IF;
4187 
4188          IF p_line_tbl (i).cancelled_flag = 'Y' THEN
4189 
4190             FOR price_adjustment_rec IN c_all_price_adjustments (p_line_tbl (i).line_id)
4191             LOOP
4192 
4193                FOR old_adjustment_rec IN
4194                    c_old_adjustment_amount (price_adjustment_rec.price_adjustment_id)
4195                LOOP
4196 
4197                   l_adj_amount := -old_adjustment_rec.amount;
4198 
4199                   IF old_adjustment_rec.amount = 0 THEN
4200                      GOTO l_endofloop;
4201                   END IF;
4202 
4203                   l_util_rec := l_empty_util_rec;
4204                   l_act_budgets_rec :=l_empty_act_budgets_rec;
4205                   l_act_budgets_rec.budget_source_type := 'OFFR';
4206                   l_act_budgets_rec.budget_source_id := old_adjustment_rec.plan_id;
4207                   l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
4208                   l_act_budgets_rec.act_budget_used_by_id := old_adjustment_rec.plan_id;
4209                   l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
4210                   l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
4211                   l_util_rec.object_type := 'ORDER';
4212                   l_util_rec.object_id   := p_line_tbl (i).header_id;
4213                   l_util_rec.product_id := p_line_tbl(i).inventory_item_id;
4214                   l_util_rec.price_adjustment_id := old_adjustment_rec.price_adjustment_id;
4215                   l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
4216                   l_util_rec.component_id :=old_adjustment_rec.plan_id;
4217                   l_util_rec.component_type := 'OFFR';
4218                   l_util_rec.currency_code :=old_adjustment_rec.currency_code;
4219                   l_util_rec.fund_id :=old_adjustment_rec.fund_id;
4220                   l_util_rec.order_line_id := p_line_tbl (i).line_id;
4221                   l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;
4222                   l_act_budgets_rec.parent_src_apprvd_amt := l_adj_amount;
4223                   l_act_budgets_rec.request_amount :=-old_adjustment_rec.plan_curr_amount;
4224                   --Fix for bug 8660000
4225                   l_act_budgets_rec.request_currency := old_adjustment_rec.plan_currency_code;
4226                   --End bug 8660000
4227                   l_util_rec.amount := l_adj_amount ;
4228                   l_util_rec.plan_curr_amount :=  l_act_budgets_rec.request_amount;
4229 
4230                   IF old_adjustment_rec.utilization_type  = 'ADJUSTMENT' THEN
4231                      l_util_rec.adjustment_type_id :=-4;
4232                      l_util_rec.adjustment_type := 'DECREASE_EARNED';
4233                      l_util_rec.orig_utilization_id := old_adjustment_rec.orig_utilization_id;
4234                   END IF;
4235                   --nirprasa, ER 8399134. Called for cancelled orders
4236                   l_util_rec.plan_currency_code :=  old_adjustment_rec.plan_currency_code;
4237                   l_util_rec.fund_request_currency_code :=  old_adjustment_rec.fund_request_currency_code;
4238                   l_util_rec.fund_request_amount :=  -old_adjustment_rec.fund_request_amount;
4239 
4240                   create_fund_utilization (
4241                         p_act_util_rec=> l_util_rec,
4242                         p_act_budgets_rec=> l_act_budgets_rec,
4243                         x_utilization_id => l_utilization_id,
4244                         x_return_status=> l_return_status,
4245                         x_msg_count=> x_msg_count,
4246                         x_msg_data=> x_msg_data
4247                      );
4248 
4249                   IF g_debug_flag = 'Y' THEN
4250                      ozf_utility_pvt.write_conc_log (
4251                        '    D: create utlization from cancelled order returns '|| l_return_status);
4252                   END IF;
4253 
4254                   IF l_return_status <> fnd_api.g_ret_sts_success THEN
4255                      GOTO l_endoflineadjloop;
4256                   END IF;
4257                   --- quit when the total earned amount is adjusted
4258                   <<l_endofloop>>
4259                   NULL;
4260                END LOOP old_adjustment_rec;
4261             END LOOP; -- end loop for price adjustment rec
4262          END IF;   -- if for cancelled flag
4263 
4264 
4265          IF p_line_tbl (i).reference_line_id IS NOT NULL
4266             --AND p_line_tbl (i).flow_status_code = 'FULFILLED'
4267             AND p_line_tbl (i).line_category_code ='RETURN'
4268             AND p_line_tbl(i).invoiced_quantity IS NOT NULL THEN
4269 
4270             IF g_debug_flag = 'Y' THEN
4271                ozf_utility_pvt.write_conc_log('    D: adjusted_changed_order: RMA with reference: ' || p_line_tbl(i).reference_line_id);
4272             END IF;
4273 
4274             OPEN c_orig_order_info (p_line_tbl (i).reference_line_id);
4275             FETCH c_orig_order_info INTO l_shipped_qty;
4276             CLOSE c_orig_order_info;
4277 
4278             FOR old_adjustment_rec IN
4279                 c_orig_adjustment_amount (p_line_tbl (i).reference_line_id)
4280             LOOP
4281 
4282                IF l_shipped_qty is NOT NULL OR l_shipped_qty <> 0 THEN
4283                   l_adj_amount := old_adjustment_rec.amount * p_line_tbl(i).invoiced_quantity/ l_shipped_qty ;
4284                END IF;
4285 
4286                IF g_debug_flag = 'Y' THEN
4287                   ozf_utility_pvt.write_conc_log(' D: adjusted_changed_order: RMA with reference: l_adj_amount    ' || l_adj_amount);
4288                END IF;
4289 
4290                IF old_adjustment_rec.amount = 0 OR l_adj_amount = 0 THEN
4291                   GOTO l_endofloop;
4292                END IF;
4293 
4294                l_util_rec := l_empty_util_rec;
4295                l_act_budgets_rec :=l_empty_act_budgets_rec;
4296                l_act_budgets_rec.budget_source_type := 'OFFR';
4297                l_act_budgets_rec.budget_source_id := old_adjustment_rec.plan_id;
4298                l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
4299                l_act_budgets_rec.act_budget_used_by_id := old_adjustment_rec.plan_id;
4300                l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
4301                l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
4302                l_util_rec.object_type := 'ORDER';
4303                l_util_rec.object_id   := p_line_tbl (i).header_id;
4304                l_util_rec.product_id := p_line_tbl(i).inventory_item_id;
4305                l_util_rec.price_adjustment_id := old_adjustment_rec.price_adjustment_id;
4306                l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
4307                l_util_rec.component_id :=old_adjustment_rec.plan_id;
4308                l_util_rec.component_type := 'OFFR';
4309                l_util_rec.currency_code :=old_adjustment_rec.currency_code;
4310                l_util_rec.fund_id :=old_adjustment_rec.fund_id;
4311                l_util_rec.order_line_id := p_line_tbl (i).line_id;
4312                l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;
4313                l_util_rec.gl_date := sysdate;
4314                l_act_budgets_rec.parent_src_apprvd_amt := l_adj_amount;
4315                l_act_budgets_rec.request_amount :=old_adjustment_rec.plan_curr_amount * p_line_tbl(i).invoiced_quantity/ l_shipped_qty ;
4316                l_act_budgets_rec.request_currency := old_adjustment_rec.plan_currency_code;
4317                l_util_rec.amount := l_adj_amount ;
4318                l_util_rec.plan_curr_amount :=  l_act_budgets_rec.request_amount;
4319                l_util_rec.adjustment_type_id :=-4;
4320                l_util_rec.adjustment_type := 'DECREASE_EARNED';
4321                l_util_rec.orig_utilization_id := old_adjustment_rec.orig_utilization_id;
4322                --nirprasa, ER 8399134. Called for returned orders
4323                l_util_rec.plan_currency_code :=  old_adjustment_rec.plan_currency_code;
4324                l_util_rec.fund_request_currency_code :=  old_adjustment_rec.fund_request_currency_code;
4325                l_util_rec.fund_request_amount :=  -old_adjustment_rec.fund_request_amount;
4326 
4327                create_fund_utilization (
4328                         p_act_util_rec=> l_util_rec,
4329                         p_act_budgets_rec=> l_act_budgets_rec,
4330                         x_utilization_id => l_utilization_id,
4331                         x_return_status=> l_return_status,
4332                         x_msg_count=> x_msg_count,
4333                         x_msg_data=> x_msg_data
4334                );
4335 
4336                IF g_debug_flag = 'Y' THEN
4337                   ozf_utility_pvt.write_conc_log (
4338                        '    D: create utlization from RMA order: ' || l_return_status);
4339                END IF;
4340 
4341                IF l_return_status <> fnd_api.g_ret_sts_success THEN
4342                   GOTO l_endoflineadjloop;
4343                END IF;
4344                   --- quit when the total earned amount is adjusted
4345                <<l_endofloop>>
4346                NULL;
4347             END LOOP old_adjustment_rec;
4348          END IF; -- end of p_line_tbl (i).reference_line_id IS NOT NULL
4349 
4350          /*
4351            Note: adjustment already posted to TM budget in adjust_accrual when line is SHIPPED or RETURN order is booked
4352                  SHIPPED LINE: if shipped quantity <> requested quantity, e.g.
4353                  Original order: quantity 10, price adjustment id 12345
4354                  During shipping, only 8 are shipped, then 2 is backordered.
4355                  2 new lines are automatically created:
4356                  one line for shipped: quantity = 8, with old price adjustment id, line operation=UPDATE
4357                  another line for backorder: quantity = 2(10-8), with new price adjustment id, line operation=CREATE
4358 
4359                  handle case for partial ship with running accrual engine before ship. added by fliu on 05/24/04 to fix bug 3357164
4360                  If running accrual engine after booking order, one record is created. then partial shipped,  two new records will be created. one with positive
4361                  for backordered amount. another with negative for adjustment from previous record.
4362            */
4363 
4364           IF p_line_tbl(i).line_id= p_old_line_tbl(i).line_id
4365              AND p_old_line_tbl(i).ordered_quantity <>p_line_tbl(i).shipped_quantity
4366              AND NVL(p_line_tbl(i).shipped_quantity,0) <> 0
4367              --AND p_line_tbl(i).flow_status_code = 'SHIPPED'
4368           THEN
4369 
4370              IF g_debug_flag = 'Y' THEN
4371                 ozf_utility_pvt.write_conc_log('    D: adjusted_changed_order: partial shipment line(line_id=' || p_line_tbl(i).line_id || ')');
4372              END IF;
4373 
4374              OPEN c_order_info (p_line_tbl (i).header_id);
4375              FETCH c_order_info INTO l_order_status, l_order_booked_flag, l_order_curr,l_order_number,l_org_id;
4376              CLOSE c_order_info;
4377 
4378              FOR price_adjustment_rec IN c_all_price_adjustments (p_line_tbl (i).line_id)
4379              LOOP
4380 
4381                 OPEN c_old_adjustment_total_amount (price_adjustment_rec.price_adjustment_id);
4382                 FETCH c_old_adjustment_total_amount INTO l_total;
4383                 CLOSE c_old_adjustment_total_amount;
4384 
4385                 IF g_debug_flag = 'Y' THEN
4386                    ozf_utility_pvt.write_conc_log('old adj total amount l_total: ' || l_total);
4387                 END IF;
4388 
4389                 IF NVL(l_total,0) = 0 THEN  -- add to fix bug 4930867.
4390                    GOTO l_endpriceadjloop;
4391                 END IF;
4392 
4393                 --kdass Bug 12946941 - For SDR, calculate adjustment amount based on Cost Price stored in Order Lines table
4394                 l_adjusted_amount := price_adjustment_rec.adjusted_amount;
4395 
4396                 OPEN  c_offer_details(price_adjustment_rec.list_header_id);
4397                 FETCH c_offer_details INTO l_custom_setup_id;
4398                 CLOSE c_offer_details;
4399 
4400                 IF g_debug_flag = 'Y' THEN
4401                    ozf_utility_pvt.write_conc_log('l_custom_setup_id: ' || l_custom_setup_id);
4402                 END IF;
4403 
4404                 IF l_custom_setup_id = 118 THEN
4405                    l_column_name := FND_PROFILE.VALUE('OZF_ITEM_COST_COLUMN');
4406 
4407                    IF l_column_name IS NOT NULL AND l_column_name <> FND_API.G_MISS_CHAR THEN
4408                       l_stmt := 'SELECT ' || l_column_name ||' FROM oe_order_lines_all  WHERE line_id = :1';
4409 
4410                       IF g_debug_flag = 'Y' THEN
4411                          ozf_utility_pvt.write_conc_log('Query to obtain purchase price ' || l_stmt);
4412                       END IF;
4413 
4414                       OPEN c_purchase_price FOR l_stmt using p_line_tbl (i).line_id;
4415                       FETCH c_purchase_price INTO l_cost_price;
4416                       CLOSE c_purchase_price;
4417                    END IF;
4418 
4419                    l_operand := price_adjustment_rec.operand;
4420                    l_arithmetic_operator := price_adjustment_rec.arithmetic_operator;
4421 
4422                    IF g_debug_flag = 'Y' THEN
4423                       ozf_utility_pvt.write_conc_log('l_cost_price: ' || l_cost_price);
4424                       ozf_utility_pvt.write_conc_log('l_operand: ' || l_operand);
4425                       ozf_utility_pvt.write_conc_log('l_arithmetic_operator: ' || l_arithmetic_operator);
4426                    END IF;
4427 
4428                    IF l_arithmetic_operator = '%' THEN
4429                       l_adjusted_amount := (NVL(l_operand, 0)) * l_cost_price / 100;
4430                    ELSIF l_arithmetic_operator = 'NEWPRICE' THEN
4431                       l_adjusted_amount := (l_cost_price - (NVL(l_operand, 0)));
4432                    ELSE
4433                       l_adjusted_amount := (NVL(l_operand, 0));
4434                    END IF;
4435 
4436                    l_adjusted_amount := -l_adjusted_amount;
4437 
4438                    IF g_debug_flag = 'Y' THEN
4439                         ozf_utility_pvt.write_conc_log('l_adjusted_amount for SDR: ' || l_adjusted_amount);
4440                    END IF;
4441 
4442                 END IF;
4443 
4444                 FOR old_adjustment_rec IN
4445                     c_old_adjustment_amount(price_adjustment_rec.price_adjustment_id)
4446                 LOOP
4447                               -- adjust unshipped amount.
4448                     IF g_debug_flag = 'Y' THEN
4449                        ozf_utility_pvt.write_conc_log (' price_adjustment_rec.adjusted_amount: '|| l_adjusted_amount ||
4450                                                        ' p_line_tbl(i).shipped_quantity: '|| p_line_tbl(i).shipped_quantity ||
4451                                                        ' old_adjustment_rec.plan_curr_amount: '|| old_adjustment_rec.plan_curr_amount ||
4452                                                        ' price_adjustment_rec.price_adjustment_id: '|| price_adjustment_rec.price_adjustment_id );
4453                     END IF;
4454 
4455                     -- add by feliu on 08/03/04 to fix  3778200
4456                     IF old_adjustment_rec.utilization_type IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT') THEN  -- new calculation for adjustment.
4457                        l_orig_adj_amount := old_adjustment_rec.plan_curr_amount *
4458                                      (1 - p_line_tbl(i).shipped_quantity / p_old_line_tbl(i).ordered_quantity) ; -- in order currency.
4459                     ELSE
4460                         -- added by Ribha for bug fix 4417084
4461                        IF p_line_tbl(i).line_category_code <> 'RETURN' THEN
4462                           l_orig_adj_amount := old_adjustment_rec.plan_curr_amount -
4463                                              ( - l_adjusted_amount * p_line_tbl(i).shipped_quantity
4464                                              * old_adjustment_rec.plan_curr_amount /l_total) ; -- in order currency.
4465                        ELSE
4466                           l_orig_adj_amount := old_adjustment_rec.plan_curr_amount -
4467                                              ( - l_adjusted_amount * (-p_line_tbl(i).shipped_quantity)
4468                                                 * old_adjustment_rec.plan_curr_amount /l_total) ; -- in order currency.
4469                        END IF;
4470                     END IF;
4471 
4472                     IF g_debug_flag = 'Y' THEN
4473                        ozf_utility_pvt.write_conc_log (' partial ship l_total: '|| l_total ||
4474                                           ' partial ship p_line_tbl(i).shipped_quantity : '|| p_line_tbl(i).shipped_quantity  ||
4475                                           ' partial ship l_orig_adj_amount: '|| l_orig_adj_amount );
4476                     END IF;
4477 
4478                     l_orig_adj_amount  := ozf_utility_pvt.currround (
4479                                     l_orig_adj_amount ,
4480                                    --nirprasa, ER 8399134, now the amount can be in offer currency also
4481                                    --so remove the order currency and get the currency from old record
4482                                    --l_order_curr
4483                                    old_adjustment_rec.plan_currency_code
4484                                   );
4485 
4486                    --nirprasa, ER 8399134
4487                    --IF l_order_curr <> old_adjustment_rec.currency_code THEN
4488                    IF old_adjustment_rec.plan_currency_code <> old_adjustment_rec.currency_code THEN
4489                        ozf_utility_pvt.convert_currency(x_return_status => l_return_status
4490                                                         ,p_from_currency => old_adjustment_rec.plan_currency_code
4491                                                         ,p_to_currency => old_adjustment_rec.currency_code
4492                                                         ,p_conv_type => old_adjustment_rec.exchange_rate_type --nirprasa Added for bug 7030415
4493                                                         ,p_from_amount =>l_orig_adj_amount
4494                                                         ,x_to_amount => l_adj_amount
4495                                                         ,x_rate => l_rate); -- in fund  currency
4496 
4497                     ELSE
4498                        l_adj_amount := l_orig_adj_amount;
4499                     END IF;
4500 
4501                     IF g_debug_flag = 'Y' THEN
4502                        ozf_utility_pvt.write_conc_log (' partial ship adj_amount: '|| l_adj_amount );
4503                     END IF;
4504 
4505                     IF NVL(l_adj_amount,0) = 0 THEN
4506                        GOTO l_endoffloop;
4507                     END IF;
4508 
4509                     l_util_rec := l_empty_util_rec;
4510                     l_act_budgets_rec :=l_empty_act_budgets_rec;
4511                     l_util_rec.object_type := 'ORDER';
4512                     l_util_rec.object_id   := p_line_tbl (i).header_id;
4513                     l_util_rec.product_id := p_line_tbl(i).inventory_item_id;
4514                     l_util_rec.price_adjustment_id := price_adjustment_rec.price_adjustment_id;
4515                     l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
4516                     l_act_budgets_rec.budget_source_type := 'OFFR';
4517                     l_act_budgets_rec.budget_source_id := old_adjustment_rec.plan_id;
4518                     l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
4519                     l_act_budgets_rec.act_budget_used_by_id := old_adjustment_rec.plan_id;
4520                     l_act_budgets_rec.parent_src_apprvd_amt := - l_adj_amount;
4521                     l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
4522                     l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
4523                     l_act_budgets_rec.request_amount :=-l_orig_adj_amount;
4524                     l_act_budgets_rec.request_currency := l_order_curr;
4525                     l_util_rec.amount := - l_adj_amount ;
4526 
4527                     --nirprasa, ER 8399134,multi-currency enhancement, keep the amount in order currency
4528                     OPEN c_offer_currency (old_adjustment_rec.plan_id);
4529                     FETCH c_offer_currency INTO l_offer_curr,l_transaction_curr_code;
4530                     CLOSE c_offer_currency;
4531 
4532                     IF l_transaction_curr_code IS NOT NULL AND l_order_curr <> l_transaction_curr_code THEN
4533                        ozf_utility_pvt.convert_currency(x_return_status => l_return_status
4534                                                         ,p_from_currency => l_order_curr
4535                                                         ,p_to_currency => l_transaction_curr_code
4536                                                         ,p_conv_type => old_adjustment_rec.exchange_rate_type --nirprasa Added for bug 7030415
4537                                                         ,p_from_amount =>l_orig_adj_amount
4538                                                         ,x_to_amount => l_offer_amount
4539                                                         ,x_rate => l_rate); -- in offer  currency
4540 
4541                     ELSE
4542                        l_offer_amount := l_orig_adj_amount;
4543                     END IF;
4544                     l_util_rec.plan_curr_amount :=  - l_offer_amount;
4545                     --nirprasa, ER 8399134
4546 
4547                     l_util_rec.component_id :=old_adjustment_rec.plan_id;
4548                     l_util_rec.component_type := 'OFFR';
4549                     l_util_rec.currency_code :=old_adjustment_rec.currency_code;
4550                     l_util_rec.fund_id :=old_adjustment_rec.fund_id;
4551                     l_util_rec.order_line_id := p_line_tbl (i).line_id;
4552                     l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;  -- 'N';
4553                     -- create adjustment , added by feliu on 08/03/04 to fix bug 3778200
4554                     IF old_adjustment_rec.utilization_type  = 'ADJUSTMENT' THEN
4555                        l_util_rec.adjustment_type_id :=-4;
4556                        l_util_rec.adjustment_type := 'DECREASE_EARNED';
4557                        l_util_rec.orig_utilization_id := old_adjustment_rec.orig_utilization_id;
4558                     END IF;
4559                     --nirprasa, ER 8399134 multi currency enhancement. partial shipment
4560                     l_util_rec.plan_currency_code :=  old_adjustment_rec.plan_currency_code;
4561                     l_util_rec.fund_request_currency_code :=  old_adjustment_rec.fund_request_currency_code;
4562 
4563                     create_fund_utilization (
4564                                      p_act_util_rec=> l_util_rec,
4565                                      p_act_budgets_rec=> l_act_budgets_rec,
4566                                      x_utilization_id => l_utilization_id,
4567                                      x_return_status=> l_return_status,
4568                                      x_msg_count=> x_msg_count,
4569                                     x_msg_data=> x_msg_data
4570                                   );
4571                     IF g_debug_flag = 'Y' THEN
4572                        ozf_utility_pvt.write_conc_log (' retrun status for create _fund_utilization of '|| l_return_status ||
4573                             ' when partial shipping. ' );
4574                     END IF;
4575 
4576                     IF l_return_status <> fnd_api.g_ret_sts_success THEN
4577                        GOTO l_endoflineadjloop;
4578                     END IF;
4579                     /* yzhao: fix bug 3778200 - partial shipment after offer adjustment.
4580                               if line is splitted to have new line for unshipped quantity, new price adjustment need to pass to the offer adjustment
4581                     */
4582                     /* adjustment should populate order_line_id */
4583                     IF old_adjustment_rec.utilization_type IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT')  THEN
4584                        -- find out the corresponding new order line id and price adjustment id
4585                        -- create positive offer adjustment for unshipped quantity, no gl posting
4586                        -- and set new price adjustment id
4587                        -- passs header_id to avoid perf issue 13742169
4588                        OPEN c_split_line(p_line_tbl (i).line_id, p_line_tbl (i).header_id);
4589                        FETCH c_split_line INTO l_new_line_id;
4590                        CLOSE c_split_line;
4591 
4592                        OPEN c_new_adj_line(l_new_line_id,old_adjustment_rec.plan_id);
4593                        FETCH c_new_adj_line INTO l_new_adj_id;
4594                        CLOSE c_new_adj_line;
4595 
4596                        OPEN c_max_utilized_id(l_new_adj_id);
4597                        FETCH c_max_utilized_id INTO  l_util_rec.orig_utilization_id;
4598                        CLOSE c_max_utilized_id;
4599                        IF g_debug_flag = 'Y' THEN
4600                           ozf_utility_pvt.write_conc_log ('create positive line for adjustment: '|| l_new_adj_id );
4601                        END IF;
4602                        l_act_budgets_rec.request_amount := -l_act_budgets_rec.request_amount;
4603                        l_act_budgets_rec.parent_src_apprvd_amt := - l_act_budgets_rec.parent_src_apprvd_amt;
4604                        l_util_rec.amount := -l_util_rec.amount;
4605                        l_util_rec.plan_curr_amount := -l_util_rec.plan_curr_amount;
4606                        l_util_rec.order_line_id := l_new_line_id;
4607                        l_util_rec.price_adjustment_id := l_new_adj_id;
4608 
4609                        IF l_util_rec.utilization_type  = 'ADJUSTMENT' THEN
4610                           l_util_rec.adjustment_type_id :=-5;
4611                           l_util_rec.adjustment_type := 'STANDARD';
4612                        END IF;
4613 
4614                        create_fund_utilization (
4615                                          p_act_util_rec=> l_util_rec,
4616                                          p_act_budgets_rec=> l_act_budgets_rec,
4617                                          x_utilization_id => l_utilization_id,
4618                                          x_return_status=> l_return_status,
4619                                          x_msg_count=> x_msg_count,
4620                                         x_msg_data=> x_msg_data
4621                                       );
4622 
4623                        IF l_return_status <> fnd_api.g_ret_sts_success THEN
4624                           GOTO l_endoflineadjloop;
4625                        END IF;
4626 
4627                     END IF;-- end loop of old_adjustment_rec.utilization_type
4628                      --- quit when the total earned amount is adjusted
4629                     <<l_endoffloop>>
4630                     NULL;
4631                 END LOOP old_adjustment_rec;
4632                 <<l_endpriceadjloop>>
4633                 NULL;
4634              END LOOP; -- end loop for price adjustment rec
4635 
4636 
4637 
4638           END IF; -- end of shipped_quantity is not equal ordered_quantity.
4639 
4640           /*  yzhao: 12/02/2003 11.5.10 post to GL based on profile TM: Create GL Entries for Orders
4641               For normal order with accrual offer
4642                   a) if profile is set to 'Shipped', post to gl when line is shipped
4643                   b) if profile is set to 'Invoiced', post to gl when line is invoiced
4644               For normal order with off invoice offer that needs to post to gl
4645                or returned order,
4646                   post to gl when line is invoiced
4647            */
4648          l_gl_date := NULL;
4649 
4650          IF g_debug_flag = 'Y' THEN
4651             ozf_utility_pvt.write_conc_log ('    D: profile to create gl entries is set to ' ||
4652                     fnd_profile.VALUE ('OZF_ORDER_GLPOST_PHASE') || ' g_order_gl_phase=' || g_order_gl_phase);
4653          END IF;
4654 
4655          --ninarasi: bug 15877269 - When the order is shipped and invoiced the flow_status_code can be 'POST BILLING ACCEPTANCE'.
4656          --So for this status the following check will not work. So commented the flow_status_code check below (refer QP bug 14785197)
4657          IF ( g_order_gl_phase = 'SHIPPED' AND p_line_tbl(i).line_category_code <> 'RETURN' AND
4658             NVL(p_line_tbl(i).shipped_quantity,0) <> 0) THEN
4659            --AND p_line_tbl(i).flow_status_code = 'SHIPPED') THEN
4660             OPEN c_actual_shipment_date(p_line_tbl(i).line_id);
4661             FETCH c_actual_shipment_date into l_gl_date, l_shipping_quantity, l_shipping_quantity_uom, l_shipping_quantity2, l_shipping_quantity_uom2, l_fulfillment_base ;
4662             CLOSE c_actual_shipment_date;
4663 
4664 	    -- Catch Weight ER
4665 	    /*OZF_UTILITY_PVT.get_catch_weight_quantity (
4666 		  p_inventory_item_id      =>   p_line_tbl(i).inventory_item_id,
4667 		  p_order_line_id	         =>   p_line_tbl(i).line_id,
4668 		  x_return_status	         =>   l_return_status,
4669 		  x_cw_quantity		         =>   l_cw_quantity,
4670 		  x_cw_quantity_uom	       =>   l_cw_quantity_uom );*/
4671 
4672 	    -- getting fulfillment_base from OE API. In case of performance issue can think of using fulfillment_base from existing cursor
4673 	    l_fulfillment_base := OE_DUAL_UOM_UTIL.get_fulfillment_base(p_line_tbl(i).line_id) ;
4674 
4675 	    IF l_fulfillment_base = 'S' THEN
4676 	       l_cw_quantity     := l_shipping_quantity;
4677 	       l_cw_quantity_uom := l_shipping_quantity_uom;
4678 	    ELSE
4679                l_cw_quantity     := NVL(l_shipping_quantity2, l_shipping_quantity);
4680 	       l_cw_quantity_uom := NVL(l_shipping_quantity_uom2, l_shipping_quantity_uom);
4681 	    END IF;
4682 
4683 	    l_sales_transaction_rec.quantity     := NVL(l_cw_quantity, p_line_tbl(i).shipped_quantity);
4684 	    l_sales_transaction_rec.uom_code     := NVL(l_cw_quantity_uom, p_line_tbl(i).order_quantity_uom);
4685             l_sales_transaction_rec.transfer_type := 'IN';
4686             -- Catch Weight ER
4687 
4688             IF g_debug_flag = 'Y' THEN
4689                ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() gl_date uses shipment date: ' || l_gl_date || ' for arrcual posting');
4690             END IF;
4691 
4692          END IF;
4693 
4694          IF l_order_number IS NULL THEN -- get order_number if null, bug fix 3917556
4695             OPEN c_order_info (p_line_tbl (i).header_id);
4696             FETCH c_order_info INTO l_order_status, l_order_booked_flag, l_order_curr,l_order_number,l_org_id;
4697             CLOSE c_order_info;
4698          END IF;
4699 
4700          IF l_gl_date IS NULL THEN
4701             IF (p_line_tbl(i).invoice_interface_status_code = 'YES' OR NVL(p_line_tbl(i).invoiced_quantity,0) <> 0) THEN
4702                OPEN c_invoice_date(p_line_tbl(i).line_id, l_order_number);
4703                FETCH c_invoice_date INTO l_gl_date;
4704                CLOSE c_invoice_date;
4705 
4706                IF l_gl_date IS NULL THEN
4707                     -- yzhao: Jun 29, 2004 if accrual engine runs before auto-invoice completes, invoice record not created in ar table
4708 
4709                   --bug 11670604 - if auto-invoice is not run, then fail gl posting and wait until autoinvoice is run
4710                   --to post to GL based on invoice date
4711                   --l_gl_date := sysdate;
4712                   IF g_debug_flag = 'Y' THEN
4713                      OZF_UTILITY_PVT.write_conc_log(': update gl posted flag to F since invoice is not created yet');
4714                  END IF;
4715                   UPDATE ozf_funds_utilized_all_b futb
4716                      SET gl_posted_flag = 'F'
4717                         ,gl_date = NULL
4718                    WHERE futb.order_line_id = p_line_tbl(i).line_id
4719                      AND futb.gl_posted_flag <> 'Y' --bug 13517522 - added this condition so that duplicate ASO message should not re-post accrual to GL
4720                      AND EXISTS(select price_adjustment_id from oe_price_adjustments where price_adjustment_id = futb.price_adjustment_id); --ninarasi fix for bug 14750730/14695150
4721 
4722                   IF g_debug_flag = 'Y' THEN
4723                      OZF_UTILITY_PVT.write_conc_log('    D: adjust_changed_order() auto-invoice not complete. gl posting failed');
4724                   END IF;
4725 
4726                ELSE
4727 
4728                   l_sales_transaction_rec.quantity   := p_line_tbl(i).invoiced_quantity;
4729 
4730                   IF g_debug_flag = 'Y' THEN
4731                      ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() gl_date uses invoice date: ' || l_gl_date || ' for arrcual posting');
4732                   END IF;
4733                END IF;
4734             END IF;
4735         END IF;
4736 
4737 
4738          IF l_gl_date IS NOT NULL THEN
4739             OPEN sales_transation_csr(p_line_tbl (i).line_id);
4740             FETCH  sales_transation_csr INTO l_sales_trans;
4741             CLOSE sales_transation_csr;
4742 
4743             IF g_debug_flag = 'Y' THEN
4744                ozf_utility_pvt.write_conc_log('    Create_Transaction: l_sales_trans:  ' ||  l_sales_trans);
4745             END IF;
4746 
4747             IF NVL(l_sales_trans,0) <> 1 THEN
4748 
4749                l_sales_transaction_rec.sold_to_cust_account_id := p_line_tbl (i).sold_to_org_id;
4750 
4751                OPEN party_id_csr(l_sales_transaction_rec.sold_to_cust_account_id);
4752                FETCH party_id_csr INTO l_sales_transaction_rec.sold_to_party_id;
4753                CLOSE party_id_csr;
4754 
4755                OPEN party_site_id_csr(p_line_tbl (i).invoice_to_org_id);
4756                FETCH party_site_id_csr INTO l_sales_transaction_rec.sold_to_party_site_id;
4757                CLOSE party_site_id_csr;
4758 
4759                l_sales_transaction_rec.ship_to_site_use_id  := p_line_tbl (i).ship_to_org_id;
4760                l_sales_transaction_rec.bill_to_site_use_id  :=p_line_tbl(i).invoice_to_org_id;
4761                --l_sales_transaction_rec.uom_code:= NVL(p_line_tbl(i).shipping_quantity_uom,p_line_tbl(i).order_quantity_uom); -- Catch Weight : moved this code up
4762                l_sales_transaction_rec.amount   := p_line_tbl(i).unit_selling_price * l_sales_transaction_rec.quantity;
4763                l_sales_transaction_rec.currency_code  :=l_order_curr;
4764                l_sales_transaction_rec.inventory_item_id := p_line_tbl(i).inventory_item_id;
4765                l_sales_transaction_rec.header_id  :=   p_line_tbl (i).header_id;
4766                l_sales_transaction_rec.line_id  := p_line_tbl (i).line_id;
4767                l_sales_transaction_rec.source_code := 'OM';
4768                IF p_line_tbl(i).line_category_code <> 'RETURN' THEN
4769                   l_sales_transaction_rec.transfer_type := 'IN';
4770                ELSE
4771                   l_sales_transaction_rec.transfer_type := 'OUT';
4772                END IF;
4773                l_sales_transaction_rec.transaction_date  := l_gl_date;--l_volume_detail_rec.transaction_date
4774                l_sales_transaction_rec.org_id := l_org_id;
4775 
4776                IF g_debug_flag = 'Y' THEN
4777                   ozf_utility_pvt.write_conc_log('   Create_Transaction' );
4778                END IF;
4779 
4780                OZF_SALES_TRANSACTIONS_PVT.Create_Transaction (
4781                                p_api_version      => 1.0
4782                               ,p_init_msg_list    => FND_API.G_FALSE
4783                               ,p_commit           => FND_API.G_FALSE
4784                               ,p_validation_level => FND_API.G_VALID_LEVEL_FULL
4785                               ,p_transaction_rec  => l_sales_transaction_rec
4786                               ,x_sales_transaction_id => l_sales_transaction_id
4787                               ,x_return_status    => l_return_status
4788                               ,x_msg_data         => x_msg_data
4789                               ,x_msg_count        => x_msg_count
4790                       );
4791 
4792                IF g_debug_flag = 'Y' THEN
4793                   ozf_utility_pvt.write_conc_log('   Create_Transaction' ||  l_return_status);
4794                END IF;
4795 
4796                IF l_return_status <> fnd_api.g_ret_sts_success THEN
4797                   GOTO l_endoflineadjloop;
4798                END IF;
4799             END IF; -- NVL(l_sales_trans,0)
4800 
4801             IF g_debug_flag = 'Y' THEN
4802                ozf_utility_pvt.write_conc_log(' recalculate_earnings: start');
4803             END IF;
4804             OPEN c_get_accrual_rec(p_line_tbl(i).line_id);
4805             LOOP
4806                FETCH c_get_accrual_rec BULK COLLECT
4807                INTO l_utilIdTbl, l_objVerTbl, l_planTypeTbl, l_utilTypeTbl, l_amountTbl
4808                     , l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
4809                     , l_excTypeTbl, l_excDateTbl, l_currCodeTbl, l_planCurrCodeTbl
4810                     , l_fundReqCurrCodeTbl, l_planCurrAmtTbl, l_planCurrAmtRemTbl
4811                     , l_univCurrAmtTbl
4812                LIMIT g_bulk_limit;
4813 
4814                -- Fix for Bug 12657908
4815                FORALL t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
4816                UPDATE ozf_funds_utilized_all_b
4817                SET gl_date = l_gl_date,
4818                 year_id = (select ent_year_id FROM OZF_TIME_ENT_YEAR
4819                                     WHERE l_gl_date between start_date and end_date)
4820                WHERE utilization_id = l_utilIdTbl(t_i);
4821 
4822                FOR t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
4823                LOOP
4824                   IF TRUNC(l_excDateTbl(t_i)) <> TRUNC(l_gl_date)
4825                      AND l_utilTypeTbl(t_i) IN ('ACCRUAL', 'LEAD_ACCRUAL','SALES_ACCRUAL','UTILIZED') THEN
4826 
4827 
4828                      l_excDateTbl(t_i) := l_gl_date;
4829                      IF g_debug_flag = 'Y' THEN
4830                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: start');
4831                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_excDateTbl(t_i) '||l_excDateTbl(t_i));
4832                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_excTypeTbl(t_i) '||l_excTypeTbl(t_i));
4833                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_orgIdTbl(t_i) '||l_orgIdTbl(t_i));
4834                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_currCodeTbl(t_i) '||l_currCodeTbl(t_i));
4835                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planCurrCodeTbl(t_i) '||l_planCurrCodeTbl(t_i));
4836                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_fundReqCurrCodeTbl(t_i) '||l_fundReqCurrCodeTbl(t_i));
4837                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_amountTbl(t_i) '||l_amountTbl(t_i));
4838                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planCurrAmtTbl(t_i) '||l_planCurrAmtTbl(t_i));
4839                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planCurrAmtRemTbl(t_i) '||l_planCurrAmtRemTbl(t_i));
4840                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_univCurrAmtTbl(t_i) '||l_univCurrAmtTbl(t_i));
4841                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_acctAmtTbl(t_i) '||l_acctAmtTbl(t_i));
4842                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planIdTbl(t_i) '||l_planIdTbl(t_i));
4843                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planTypeTbl(t_i) '||l_planTypeTbl(t_i));
4844                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_fundIdTbl(t_i) '||l_fundIdTbl(t_i));
4845                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_utilIdTbl(t_i) '||l_utilIdTbl(t_i));
4846                         ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_utilTypeTbl(t_i) '||l_utilTypeTbl(t_i));
4847                       END IF;
4848                      recalculate_earnings(p_exchange_rate_date     => l_excDateTbl(t_i),
4849                                           p_exchange_rate_type     => l_excTypeTbl(t_i),
4850                                           p_util_org_id            => l_orgIdTbl(t_i),
4851                                           p_currency_code          => l_currCodeTbl(t_i),
4852                                           p_plan_currency_code     => l_planCurrCodeTbl(t_i),
4853                                           p_fund_req_currency_code => l_fundReqCurrCodeTbl(t_i),
4854                                           p_amount                 => l_amountTbl(t_i),
4855                                           p_plan_curr_amount       => l_planCurrAmtTbl(t_i),
4856                                           p_plan_curr_amount_rem   => l_planCurrAmtRemTbl(t_i),
4857                                           p_univ_curr_amount       => l_univCurrAmtTbl(t_i),
4858                                           p_acctd_amount           => l_acctAmtTbl(t_i),
4859                                           p_fund_req_amount        => l_planAmtTbl(t_i),
4860                                           p_util_plan_id           => l_planIdTbl(t_i),
4861                                           p_util_plan_type         => l_planTypeTbl(t_i),
4862                                           p_util_fund_id           => l_fundIdTbl(t_i),
4863                                           p_util_utilization_id    => l_utilIdTbl(t_i),
4864                                           p_util_utilization_type  => l_utilTypeTbl(t_i),
4865                                           x_return_status          => l_return_status,
4866                                           x_msg_count              => x_msg_count,
4867                                           x_msg_data               => x_msg_data);
4868                      IF g_debug_flag = 'Y' THEN
4869                         ozf_utility_pvt.write_conc_log(' recalculate_earnings returns ' || l_return_status
4870                              );
4871                         ozf_utility_pvt.write_conc_log(' l_planAmtTbl(t_i) ' || l_planAmtTbl(t_i));
4872                      END IF;
4873                   END IF;
4874                   IF l_amountTbl(t_i) <> 0 THEN--nepanda --Fix for bug 8994266
4875                   post_accrual_to_gl(        p_util_utilization_id          => l_utilIdTbl(t_i)
4876                                            , p_util_object_version_number => l_objVerTbl(t_i)
4877                                            , p_util_amount                => l_amountTbl(t_i)
4878                                            , p_util_plan_type             => l_planTypeTbl(t_i)
4879                                            , p_util_plan_id               => l_planIdTbl(t_i)
4880                                            , p_util_plan_amount           => l_planAmtTbl(t_i)
4881                                            , p_util_utilization_type      => l_utilTypeTbl(t_i)
4882                                            , p_util_fund_id               => l_fundIdTbl(t_i)
4883                                            , p_util_acctd_amount          => l_acctAmtTbl(t_i)
4884                                            , p_util_org_id                => l_orgIdTbl(t_i)
4885                                            , x_gl_posted_flag             => l_gl_posted_flag
4886                                            , x_return_status              => l_return_status
4887                                            , x_msg_count                  => x_msg_count
4888                                            , x_msg_data                   => x_msg_data
4889                                        );
4890 
4891                          -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
4892                   IF g_debug_flag = 'Y' THEN
4893                      ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() processing invoiced/shipped line ' || p_line_tbl(i).line_id
4894                              || '  post_accrual_to_gl(util_id=' || l_utilIdTbl(t_i) || ') returns ' || l_return_status
4895                              || '  x_gl_posted_flag=' || l_gl_posted_flag);
4896                   END IF;
4897                          -- yzhao: 03/04/2004 post gl for related accruals from offer adjustment or object reconcile
4898                   IF l_return_status = fnd_api.g_ret_sts_success AND l_gl_posted_flag = G_GL_FLAG_YES THEN
4899                      post_related_accrual_to_gl(
4900                                 p_utilization_id              => l_utilIdTbl(t_i)
4901                               , p_utilization_type            => l_utilTypeTbl(t_i)
4902                               , p_gl_date                     => l_gl_date
4903                               , x_return_status               => l_return_status
4904                               , x_msg_count                   => x_msg_count
4905                               , x_msg_data                    => x_msg_data
4906                            );
4907                   END IF;
4908                   ELSE--if amount is zero then only update gl_posted_flag to Y in ozf_funds_utilized_all and do not insert record to ozf_ae_lines_all
4909                   UPDATE ozf_funds_utilized_all_b
4910                         SET last_update_date = SYSDATE
4911                           , last_updated_by = NVL (fnd_global.user_id, -1)
4912                           , last_update_login = NVL (fnd_global.conc_login_id, -1)
4913                           , object_version_number = l_objVerTbl(t_i) + 1
4914                           , gl_posted_flag = G_GL_FLAG_YES
4915                         WHERE utilization_id = l_utilIdTbl(t_i)
4916                         AND   object_version_number = l_objVerTbl(t_i);
4917                   END IF; --IF l_amountTbl(t_i) <> 0 THEN --nepanda Fix for bug 8994266
4918                 END LOOP; -- FOR t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
4919 
4920                 EXIT WHEN c_get_accrual_rec%NOTFOUND;
4921             END LOOP;  -- bulk fetch
4922             CLOSE c_get_accrual_rec;
4923 
4924          END IF;  -- IF l_gl_date IS NOT NULL
4925 
4926          <<l_endoflineadjloop>>
4927          IF l_return_status <> fnd_api.g_ret_sts_success THEN
4928             -- Write Relelvant Messages
4929             IF g_debug_flag = 'Y' THEN
4930                 ozf_utility_pvt.write_conc_log (
4931                ' /*************************** DEBUG MESSAGE END *************************/' ||
4932                ' /****** Offer Adjustment For Line(id=' || p_line_tbl(i).line_id || ') failed  with the following Errors *******/');
4933             END IF;
4934 
4935             -- Dump All the MEssages from the Message list
4936             ozf_utility_pvt.write_conc_log;
4937             -- Initialize the Message list for NExt Processing
4938             fnd_msg_pub.initialize;
4939             ROLLBACK TO line_adjustment;
4940             -- return a status error
4941             x_return_status := fnd_api.g_ret_sts_error ;
4942             --5/30/2002  Added to exit the loop because we want to perform handle exception to put the  me
4943             -- go out of the loop because we put this message in the exception queue
4944             EXIT;
4945          ELSIF  l_return_status = fnd_api.g_ret_sts_success THEN
4946             IF g_debug_flag = 'Y' THEN
4947                ozf_utility_pvt.write_conc_log (' /*************************** DEBUG MESSAGE END *********************/'||
4948                    ' /****** Line Adjustment Success *******/ p_line_tbl(i).line_id  '   || p_line_tbl(i).line_id );
4949             END IF;
4950          ELSE
4951            IF g_debug_flag = 'Y' THEN
4952               ozf_utility_pvt.write_conc_log ( '    D: Line Return Status ' ||l_return_status);
4953            END IF;
4954 
4955          END IF;
4956 
4957       END LOOP new_line_tbl_loop;
4958 
4959       -- Standard call to get message count and IF count is 1, get message info.
4960       fnd_msg_pub.count_and_get (
4961          p_count=> x_msg_count,
4962          p_data=> x_msg_data,
4963          p_encoded=> fnd_api.g_false
4964       );
4965    EXCEPTION
4966       --nepanda : Added exception block for normal errors and unexpected errors, before checking for OTHERS
4967      WHEN fnd_api.g_exc_error THEN
4968          x_return_status            := fnd_api.g_ret_sts_error;
4969          ozf_utility_pvt.write_conc_log (' /**************EXCEPTION in ozf_accrual_engine.adjust_changed_order');
4970          fnd_msg_pub.count_and_get (
4971             p_count=> x_msg_count,
4972             p_data=> x_msg_data,
4973             p_encoded=> fnd_api.g_false
4974          );
4975       WHEN fnd_api.g_exc_unexpected_error THEN
4976          x_return_status            := fnd_api.g_ret_sts_unexp_error;
4977 
4978          ozf_utility_pvt.write_conc_log (' /**************UNEXPECTED EXCEPTION in ozf_accrual_engine.adjust_changed_order');
4979          ozf_utility_pvt.write_conc_log('    D: adjust_changed_order: exception. errcode=' || sqlcode || '  msg: ' || substr(sqlerrm, 1, 3000));
4980 
4981          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
4982             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
4983          END IF;
4984 
4985         fnd_msg_pub.count_and_get (
4986             p_count=> x_msg_count,
4987             p_data=> x_msg_data,
4988             p_encoded=> fnd_api.g_false
4989          );
4990       WHEN OTHERS THEN
4991          x_return_status            := fnd_api.g_ret_sts_unexp_error;
4992 
4993          ozf_utility_pvt.write_conc_log (' /**************UNEXPECTED EXCEPTION in ozf_accrual_engine.adjust_changed_order');
4994          ozf_utility_pvt.write_conc_log('    D: adjust_changed_order: exception. errcode=' || sqlcode || '  msg: ' || substr(sqlerrm, 1, 3000));
4995 
4996          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
4997             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
4998          END IF;
4999 
5000          fnd_msg_pub.count_and_get (
5001             p_count=> x_msg_count,
5002             p_data=> x_msg_data,
5003             p_encoded=> fnd_api.g_false
5004          );
5005    END adjust_changed_order;
5006 
5007    ------------------------------------------------------------------------------
5008 -- Procedure Name
5009 --   Get_Exception_Message
5010 -- Purpose
5011 --   This procedure collects order updates FROM the Order Capture NotIFication
5012 --   API. Started FROM a concurrent process, it is a loop which
5013 --   gets the latest notIFication off of the queue.
5014 --
5015 -- History
5016 --   4/30/2002 mpande Created
5017 ------------------------------------------------------------------------------
5018    PROCEDURE get_exception_message (x_errbuf OUT NOCOPY VARCHAR2, x_retcode OUT NUMBER);
5019 ------------------------------------------------------------------------------
5020 -- Procedure Name
5021 --   Get_Message
5022 -- Purpose
5023 --   This procedure collects order updates FROM the Order Capture NotIFication
5024 --   API. Started FROM a concurrent process, it is a loop which
5025 --   gets the latest notIFication off of the queue.
5026 --   p_run_exception IN VARCHAR2
5027 --    Can Have 2 values : 'N' Run Only Messages Donot Run Exception Messages
5028 --                      : 'Y' Run Both Message and Exception  DEFAULT
5029 -- History
5030 --   06-20-00  pjindal Created
5031 --   06-20-00  updated message handling and error handling
5032 --   5/6/2002  Added one more parameter to run exception messages
5033 ------------------------------------------------------------------------------
5034    PROCEDURE get_message (x_errbuf OUT NOCOPY VARCHAR2,
5035                           x_retcode OUT NOCOPY NUMBER,
5036                           p_run_exception IN VARCHAR2 := 'N',
5037                           p_debug     IN VARCHAR2 := 'N'
5038                          ) IS
5039       l_return_status              VARCHAR2 (1);
5040       l_process_audit_id           NUMBER;
5041       l_msg_count                  NUMBER;
5042       l_msg_data                   VARCHAR2 (2000);
5043       l_no_more_messages           VARCHAR2 (1);
5044       l_header_id                  NUMBER;
5045       l_booked_flag                VARCHAR2 (1);
5046       l_header_rec                 oe_order_pub.header_rec_type;
5047       l_old_header_rec             oe_order_pub.header_rec_type;
5048       l_header_adj_tbl             oe_order_pub.header_adj_tbl_type;
5049       l_old_header_adj_tbl         oe_order_pub.header_adj_tbl_type;
5050       l_header_price_att_tbl       oe_order_pub.header_price_att_tbl_type;
5051       l_old_header_price_att_tbl   oe_order_pub.header_price_att_tbl_type;
5052       l_header_adj_att_tbl         oe_order_pub.header_adj_att_tbl_type;
5053       l_old_header_adj_att_tbl     oe_order_pub.header_adj_att_tbl_type;
5054       l_header_adj_assoc_tbl       oe_order_pub.header_adj_assoc_tbl_type;
5055       l_old_header_adj_assoc_tbl   oe_order_pub.header_adj_assoc_tbl_type;
5056       l_header_scredit_tbl         oe_order_pub.header_scredit_tbl_type;
5057       l_old_header_scredit_tbl     oe_order_pub.header_scredit_tbl_type;
5058       l_line_tbl                   oe_order_pub.line_tbl_type;
5059       l_old_line_tbl               oe_order_pub.line_tbl_type;
5060       l_line_adj_tbl               oe_order_pub.line_adj_tbl_type;
5061       l_old_line_adj_tbl           oe_order_pub.line_adj_tbl_type;
5062       l_line_price_att_tbl         oe_order_pub.line_price_att_tbl_type;
5063       l_old_line_price_att_tbl     oe_order_pub.line_price_att_tbl_type;
5064       l_line_adj_att_tbl           oe_order_pub.line_adj_att_tbl_type;
5065       l_old_line_adj_att_tbl       oe_order_pub.line_adj_att_tbl_type;
5066       l_line_adj_assoc_tbl         oe_order_pub.line_adj_assoc_tbl_type;
5067       l_old_line_adj_assoc_tbl     oe_order_pub.line_adj_assoc_tbl_type;
5068       l_line_scredit_tbl           oe_order_pub.line_scredit_tbl_type;
5069       l_old_line_scredit_tbl       oe_order_pub.line_scredit_tbl_type;
5070       l_lot_serial_tbl             oe_order_pub.lot_serial_tbl_type;
5071       l_old_lot_serial_tbl         oe_order_pub.lot_serial_tbl_type;
5072       l_action_request_tbl         oe_order_pub.request_tbl_type;
5073       l_que_msg_count              NUMBER := 0 ;
5074    BEGIN
5075       -- Standard Start of process savepoint
5076       -- Start looping to check for messages in the queue
5077       fnd_msg_pub.initialize;
5078       g_debug_flag := p_debug ;
5079 
5080       SAVEPOINT get_message_savepoint;
5081 
5082       <<message_loop>>
5083 
5084       LOOP
5085          -- Queue savepoint for standard advanced queue error handling
5086          BEGIN
5087          SAVEPOINT get_message_loop_savepoint;
5088 
5089          ozf_utility_pvt.write_conc_log ('STARTING MESSAGE QUEUE');
5090 
5091          --
5092          -- Invoke Get_Mesage to dequeue queue payload and return Order data
5093          --
5094          aso_order_feedback_pub.get_notice (
5095             p_api_version=> 1.0,
5096             x_return_status=> l_return_status,
5097             x_msg_count=> l_msg_count,
5098             x_msg_data=> l_msg_data,
5099             p_app_short_name=> 'OZF' -- need to be resolved , wether it is AMS or OZF
5100                                     ,
5101             x_no_more_messages=> l_no_more_messages,
5102             x_header_rec=> l_header_rec,
5103             x_old_header_rec=> l_old_header_rec,
5104             x_header_adj_tbl=> l_header_adj_tbl,
5105             x_old_header_adj_tbl=> l_old_header_adj_tbl,
5106             x_header_price_att_tbl=> l_header_price_att_tbl,
5107             x_old_header_price_att_tbl=> l_old_header_price_att_tbl,
5108             x_header_adj_att_tbl=> l_header_adj_att_tbl,
5109             x_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
5110             x_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
5111             x_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
5112             x_header_scredit_tbl=> l_header_scredit_tbl,
5113             x_old_header_scredit_tbl=> l_old_header_scredit_tbl,
5114             x_line_tbl=> l_line_tbl,
5115             x_old_line_tbl=> l_old_line_tbl,
5116             x_line_adj_tbl=> l_line_adj_tbl,
5117             x_old_line_adj_tbl=> l_old_line_adj_tbl,
5118             x_line_price_att_tbl=> l_line_price_att_tbl,
5119             x_old_line_price_att_tbl=> l_old_line_price_att_tbl,
5120             x_line_adj_att_tbl=> l_line_adj_att_tbl,
5121             x_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
5122             x_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
5123             x_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
5124             x_line_scredit_tbl=> l_line_scredit_tbl,
5125             x_old_line_scredit_tbl=> l_old_line_scredit_tbl,
5126             x_lot_serial_tbl=> l_lot_serial_tbl,
5127             x_old_lot_serial_tbl=> l_old_lot_serial_tbl,
5128             x_action_request_tbl=> l_action_request_tbl
5129          );
5130          --
5131          --///added by mpande to write a error message to the list
5132          --if not sucess add a error message to th emessage listx
5133          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
5134             ozf_utility_pvt.write_conc_log ('Queue Return Error ');
5135 
5136             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
5137                fnd_message.set_name ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK_FAIL');
5138                fnd_msg_pub.ADD;
5139             END IF;
5140             ozf_utility_pvt.write_conc_log;
5141             RETURN;
5142          END IF;
5143          -- Check return status
5144          -- if success call adjust_accrual
5145          --
5146          IF l_return_status = fnd_api.g_ret_sts_success THEN
5147             IF (l_line_adj_tbl.COUNT <> 0) THEN
5148                IF g_debug_flag = 'Y' THEN
5149                   ozf_utility_pvt.write_conc_log ('ADJUSTMENT ');
5150                END IF;
5151 
5152                adjust_accrual (
5153                   p_api_version=> 1.0
5154                  ,p_init_msg_list=> fnd_api.g_true
5155                  ,x_return_status=> l_return_status
5156                  ,x_msg_count=> l_msg_count
5157                  ,x_msg_data=> l_msg_data
5158                  ,p_line_adj_tbl=> l_line_adj_tbl
5159                  ,p_old_line_adj_tbl=> l_old_line_adj_tbl
5160                  ,p_header_rec=> l_header_rec
5161                );
5162                IF g_debug_flag = 'Y' THEN
5163                   ozf_utility_pvt.write_conc_log (   'ADJUSTMENT STATUS ' || l_return_status);
5164                END IF;
5165             END IF;
5166          END IF;
5167          --l_return_status := fnd_api.g_ret_sts_success;
5168          IF l_return_status = fnd_api.g_ret_sts_success THEN
5169             IF (l_line_tbl.COUNT <> 0) THEN
5170                IF g_debug_flag = 'Y' THEN
5171                   ozf_utility_pvt.write_conc_log ('LINE');
5172                END IF;
5173                adjust_changed_order (
5174                   p_api_version=> 1.0
5175                  ,p_init_msg_list=> fnd_api.g_true
5176                  ,x_return_status=> l_return_status
5177                  ,x_msg_count=> l_msg_count
5178                  ,x_msg_data=> l_msg_data
5179                  ,p_header_rec=> l_header_rec
5180                  ,p_old_header_rec=> l_old_header_rec
5181                  ,p_line_tbl=> l_line_tbl
5182                  ,p_old_line_tbl=> l_old_line_tbl
5183                );
5184                IF g_debug_flag = 'Y' THEN
5185                   ozf_utility_pvt.write_conc_log (                 'LINE STATUS '          || l_return_status       );
5186                END IF;
5187             END IF;
5188          END IF;
5189        -- Call to Volume Offer adjustment.
5190         --
5191 
5192          IF l_no_more_messages = 'T' THEN
5193             ozf_utility_pvt.write_conc_log (   'NO MORE MESSAGES IN THE QUEUE ' || l_no_more_messages);
5194          END IF;
5195          --
5196          -- Check return status of functional process,
5197          -- rollback to undo processing
5198          -- if not success write the error message to the log file
5199 
5200          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
5201             --fnd_file.put_line(--fnd_file.log, 'before writinf concurrenct log '||l_return_status);
5202             ozf_utility_pvt.write_conc_log ('D: Error in one of the process');
5203 
5204             ROLLBACK TO get_message_loop_savepoint;
5205             x_retcode                  := 1;
5206             x_errbuf                   := l_msg_data;
5207          END IF;
5208 
5209          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
5210             /*Enqueue the failed message into the Order Feedback Exception Queue. This data
5211             can be dequeued subsequently by using the GET_EXCEPTION API */
5212             IF g_debug_flag = 'Y' THEN
5213                ozf_utility_pvt.write_conc_log ('In handle queue exception ');
5214             END IF;
5215             aso_order_feedback_pub.handle_exception (
5216                p_api_version=> 1.0,
5217                p_init_msg_list=> fnd_api.g_false,
5218                p_commit=> fnd_api.g_false,
5219                x_return_status=> l_return_status,
5220                x_msg_count=> l_msg_count,
5221                x_msg_data=> l_msg_data,
5222                p_app_short_name=> 'OZF',
5223                p_header_rec=> l_header_rec,
5224                p_old_header_rec=> l_old_header_rec,
5225                p_header_adj_tbl=> l_header_adj_tbl,
5226                p_old_header_adj_tbl=> l_old_header_adj_tbl,
5227                p_header_price_att_tbl=> l_header_price_att_tbl,
5228                p_old_header_price_att_tbl=> l_old_header_price_att_tbl,
5229                p_header_adj_att_tbl=> l_header_adj_att_tbl,
5230                p_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
5231                p_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
5232                p_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
5233                p_header_scredit_tbl=> l_header_scredit_tbl,
5234                p_old_header_scredit_tbl=> l_old_header_scredit_tbl,
5235                p_line_tbl=> l_line_tbl,
5236                p_old_line_tbl=> l_old_line_tbl,
5237                p_line_adj_tbl=> l_line_adj_tbl,
5238                p_old_line_adj_tbl=> l_old_line_adj_tbl,
5239                p_line_price_att_tbl=> l_line_price_att_tbl,
5240                p_old_line_price_att_tbl=> l_old_line_price_att_tbl,
5241                p_line_adj_att_tbl=> l_line_adj_att_tbl,
5242                p_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
5243                p_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
5244                p_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
5245                p_line_scredit_tbl=> l_line_scredit_tbl,
5246                p_old_line_scredit_tbl=> l_old_line_scredit_tbl,
5247                p_lot_serial_tbl=> l_lot_serial_tbl,
5248                p_old_lot_serial_tbl=> l_old_lot_serial_tbl,
5249                p_action_request_tbl=> l_action_request_tbl
5250             );
5251          END IF;
5252          -- Quit the procedure IF the queue is empty
5253          ozf_utility_pvt.write_conc_log (' /*************************** END OF QUEUE MESSAGE  *************************/');
5254 
5255          EXIT WHEN l_return_status = fnd_api.g_ret_sts_unexp_error;
5256          EXIT WHEN l_no_more_messages = fnd_api.g_true;
5257          l_que_msg_count := l_que_msg_count + 1 ;
5258          EXIT WHEN l_que_msg_count = g_message_count; --nirprasa, added for bug 8435487 FP of bug 8218560
5259          IF l_return_status = fnd_api.g_ret_sts_success THEN
5260             COMMIT;
5261             x_retcode                  := 0;
5262          END IF;
5263          EXCEPTION
5264          WHEN FND_API.G_EXC_ERROR THEN
5265             ROLLBACK TO get_message_loop_savepoint;
5266             ozf_utility_pvt.write_conc_log('FALIED');
5267             ozf_utility_pvt.write_conc_log;
5268 
5269         WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
5270             ROLLBACK TO get_message_loop_savepoint;
5271             ozf_utility_pvt.write_conc_log('FALIED');
5272             ozf_utility_pvt.write_conc_log;
5273 
5274         WHEN OTHERS THEN
5275             ROLLBACK TO get_message_loop_savepoint;
5276             ozf_utility_pvt.write_conc_log('FAILED');
5277             IF FND_MSG_PUB.Check_Msg_level (FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW) THEN
5278                FND_MESSAGE.Set_Name('OZF','OZF_API_DEBUG_MESSAGE');
5279                FND_MESSAGE.Set_Token('TEXT',sqlerrm);
5280                FND_MSG_PUB.Add;
5281             END IF;
5282             ozf_utility_pvt.write_conc_log;
5283 
5284          END;
5285       END LOOP message_loop;
5286 
5287       ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED '|| to_char(l_que_msg_count) || ' MESSAGES ');
5288       -- move except message from begining to last to fix issue for double creating accrual when same messsages
5289       -- in both exception queue and normal queue. by feliu on 12/30/2005
5290       IF p_run_exception = 'Y' THEN
5291 
5292          ozf_utility_pvt.write_conc_log ('START Exception Message ....... '|| x_retcode);
5293 
5294          ozf_utility_pvt.write_conc_log ('<====EXCEPTION QUEUE START TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5295 
5296          get_exception_message(x_errbuf , x_retcode);
5297 
5298          ozf_utility_pvt.write_conc_log ('END Exception Message Return Code'|| x_retcode);
5299 
5300          ozf_utility_pvt.write_conc_log ('<====EXCEPTION QUEUE END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5301 
5302       END IF;
5303 
5304 
5305    EXCEPTION
5306       WHEN fnd_api.g_exc_error THEN
5307         ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED ' ||to_char(l_que_msg_count) ||'MESSAGES' );
5308         x_retcode := 1;
5309       WHEN fnd_api.g_exc_unexpected_error THEN
5310         ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED ' ||to_char(l_que_msg_count) || 'MESSAGES' );
5311         x_retcode := 1;
5312       WHEN OTHERS THEN
5313         ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED '|| to_char(l_que_msg_count) ||'MESSAGES' );
5314         x_retcode := 1;
5315 
5316    END get_message;
5317    ------------------------------------------------------------------------------
5318 -- Procedure Name
5319 --   Get_Exception_Message
5320 -- Purpose
5321 --   This procedure collects order updates FROM the Order Capture NotIFication
5322 --   API. Started FROM a concurrent process, it is a loop which
5323 --   gets the latest notIFication off of the queue.
5324 --
5325 -- History
5326 --   4/30/2002 mpande Created
5327 ------------------------------------------------------------------------------
5328    PROCEDURE get_exception_message (x_errbuf OUT NOCOPY VARCHAR2,
5329                                     x_retcode OUT NOCOPY NUMBER
5330    )  IS
5331       l_return_status              VARCHAR2 (1);
5332       l_process_audit_id           NUMBER;
5333       l_msg_count                  NUMBER;
5334       l_msg_data                   VARCHAR2 (2000);
5335       l_no_more_messages           VARCHAR2 (1);
5336       l_header_id                  NUMBER;
5337       l_booked_flag                VARCHAR2 (1);
5338       l_header_rec                 oe_order_pub.header_rec_type;
5339       l_old_header_rec             oe_order_pub.header_rec_type;
5340       l_header_adj_tbl             oe_order_pub.header_adj_tbl_type;
5341       l_old_header_adj_tbl         oe_order_pub.header_adj_tbl_type;
5342       l_header_price_att_tbl       oe_order_pub.header_price_att_tbl_type;
5343       l_old_header_price_att_tbl   oe_order_pub.header_price_att_tbl_type;
5344       l_header_adj_att_tbl         oe_order_pub.header_adj_att_tbl_type;
5345       l_old_header_adj_att_tbl     oe_order_pub.header_adj_att_tbl_type;
5346       l_header_adj_assoc_tbl       oe_order_pub.header_adj_assoc_tbl_type;
5347       l_old_header_adj_assoc_tbl   oe_order_pub.header_adj_assoc_tbl_type;
5348       l_header_scredit_tbl         oe_order_pub.header_scredit_tbl_type;
5349       l_old_header_scredit_tbl     oe_order_pub.header_scredit_tbl_type;
5350       l_line_tbl                   oe_order_pub.line_tbl_type;
5351       l_old_line_tbl               oe_order_pub.line_tbl_type;
5352       l_line_adj_tbl               oe_order_pub.line_adj_tbl_type;
5353       l_old_line_adj_tbl           oe_order_pub.line_adj_tbl_type;
5354       l_line_price_att_tbl         oe_order_pub.line_price_att_tbl_type;
5355       l_old_line_price_att_tbl     oe_order_pub.line_price_att_tbl_type;
5356       l_line_adj_att_tbl           oe_order_pub.line_adj_att_tbl_type;
5357       l_old_line_adj_att_tbl       oe_order_pub.line_adj_att_tbl_type;
5358       l_line_adj_assoc_tbl         oe_order_pub.line_adj_assoc_tbl_type;
5359       l_old_line_adj_assoc_tbl     oe_order_pub.line_adj_assoc_tbl_type;
5360       l_line_scredit_tbl           oe_order_pub.line_scredit_tbl_type;
5361       l_old_line_scredit_tbl       oe_order_pub.line_scredit_tbl_type;
5362       l_lot_serial_tbl             oe_order_pub.lot_serial_tbl_type;
5363       l_old_lot_serial_tbl         oe_order_pub.lot_serial_tbl_type;
5364       l_action_request_tbl         oe_order_pub.request_tbl_type;
5365       l_index   NUMBER;
5366       l_mode                       VARCHAR2(30):= DBMS_AQ.BROWSE;
5367       l_navigation                 VARCHAR2 (30) := DBMS_AQ.FIRST_MESSAGE;
5368 
5369    BEGIN
5370       -- Standard Start of process savepoint
5371       -- Start looping to check for messages in the queue
5372       fnd_msg_pub.initialize;
5373       SAVEPOINT get_message_savepoint;
5374       -- dequeue the exception queue
5375       <<exception_loop>>
5376       LOOP
5377          ozf_utility_pvt.write_conc_log ('In Queue Exception ');
5378 
5379          -- Queue savepoint for standard advanced queue error handling
5380          BEGIN
5381          SAVEPOINT get_excep_loop_savepoint;
5382          --
5383          -- Invoke Get_Mesage to dequeue queue payload and return Order data
5384          --
5385          aso_order_feedback_pub.get_exception (
5386             p_api_version=> 1.0,
5387             x_return_status=> l_return_status,
5388             x_msg_count=> l_msg_count,
5389             x_msg_data=> l_msg_data,
5390             p_app_short_name=> 'OZF', -- need to be resolved , wether it is AMS or OZF
5391             p_dequeue_mode  => l_mode,
5392             p_navigation   => l_navigation ,
5393             x_no_more_messages=> l_no_more_messages,
5394             x_header_rec=> l_header_rec,
5395             x_old_header_rec=> l_old_header_rec,
5396             x_header_adj_tbl=> l_header_adj_tbl,
5397             x_old_header_adj_tbl=> l_old_header_adj_tbl,
5398             x_header_price_att_tbl=> l_header_price_att_tbl,
5399             x_old_header_price_att_tbl=> l_old_header_price_att_tbl,
5400             x_header_adj_att_tbl=> l_header_adj_att_tbl,
5401             x_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
5402             x_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
5403             x_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
5404             x_header_scredit_tbl=> l_header_scredit_tbl,
5405             x_old_header_scredit_tbl=> l_old_header_scredit_tbl,
5406             x_line_tbl=> l_line_tbl,
5407             x_old_line_tbl=> l_old_line_tbl,
5408             x_line_adj_tbl=> l_line_adj_tbl,
5409             x_old_line_adj_tbl=> l_old_line_adj_tbl,
5410             x_line_price_att_tbl=> l_line_price_att_tbl,
5411             x_old_line_price_att_tbl=> l_old_line_price_att_tbl,
5412             x_line_adj_att_tbl=> l_line_adj_att_tbl,
5413             x_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
5414             x_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
5415             x_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
5416             x_line_scredit_tbl=> l_line_scredit_tbl,
5417             x_old_line_scredit_tbl=> l_old_line_scredit_tbl,
5418             x_lot_serial_tbl=> l_lot_serial_tbl,
5419             x_old_lot_serial_tbl=> l_old_lot_serial_tbl,
5420             x_action_request_tbl=> l_action_request_tbl
5421          );
5422          --
5423          --ozf_utility_pvt.debug_message('l_return_status  ='||l_return_status );
5424          --///added by mpande to write a error message to the list
5425          --if not sucess add a error message to th emessage list
5426          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
5427              IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
5428                fnd_message.set_name ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK_FAIL');
5429                fnd_msg_pub.ADD;
5430             END IF;
5431             ozf_utility_pvt.write_conc_log;
5432             RETURN;
5433          END IF;
5434          -- Check return status
5435          -- if success call adjust_accrual
5436          --
5437          IF l_return_status = fnd_api.g_ret_sts_success THEN
5438             IF (l_line_adj_tbl.COUNT <> 0) THEN
5439                 ozf_utility_pvt.write_conc_log ('In get exception adjustment');
5440 
5441                adjust_accrual (
5442                   p_api_version=> 1.0,
5443                   p_init_msg_list=> fnd_api.g_true,
5444                   x_return_status=> l_return_status,
5445                   x_msg_count=> l_msg_count,
5446                   x_msg_data=> l_msg_data,
5447                   p_line_adj_tbl=> l_line_adj_tbl,
5448                   p_old_line_adj_tbl=> l_old_line_adj_tbl,
5449                   p_header_rec=> l_header_rec,
5450                   p_exception_queue    => fnd_api.g_true
5451                );
5452                ozf_utility_pvt.write_conc_log ('ADJUSTMENT EXCEPTION STATUS'||l_return_status);
5453 
5454             END IF;
5455          END IF;
5456          IF l_return_status = fnd_api.g_ret_sts_success THEN
5457             IF (l_line_tbl.COUNT <> 0) THEN
5458                ozf_utility_pvt.write_conc_log ('    D: EXCEPTON QUEUE Start processing line');
5459 
5460                adjust_changed_order (
5461                   p_api_version=> 1.0,
5462                   p_init_msg_list=> fnd_api.g_true,
5463                   x_return_status=> l_return_status,
5464                   x_msg_count=> l_msg_count,
5465                   x_msg_data=> l_msg_data,
5466                   p_header_rec=> l_header_rec,
5467                   p_old_header_rec=> l_old_header_rec,
5468                   p_line_tbl=> l_line_tbl,
5469                   p_old_line_tbl=> l_old_line_tbl
5470                );
5471                ozf_utility_pvt.write_conc_log ('    D: EXCEPTION QUEUE PROCESSING LINE RETURNS STATUS'||l_return_status);
5472 
5473             END IF;
5474          END IF;
5475 
5476          IF l_no_more_messages = 'T' THEN
5477             ozf_utility_pvt.write_conc_log (   'NO MORE MESSAGES IN THE QUEUE '
5478                                          || l_no_more_messages);
5479          END IF;
5480          -- write_conc_log;
5481          --
5482          -- Check return status of functional process,
5483          -- rollback to undo processing
5484          -- if not success write the error message to the log file
5485          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
5486             l_navigation  := DBMS_AQ.NEXT_MESSAGE;
5487             ROLLBACK TO get_excep_loop_savepoint;
5488             --x_retcode                  := 1;
5489             x_errbuf                   := l_msg_data;
5490          END IF;
5491          -- Quit the procedure IF the queue is empty
5492          EXIT WHEN l_return_status = fnd_api.g_ret_sts_unexp_error;
5493          EXIT WHEN l_no_more_messages = fnd_api.g_true;
5494 
5495          IF l_return_status = fnd_api.g_ret_sts_success THEN
5496 
5497             aso_order_feedback_pub.get_exception (
5498                p_api_version=> 1.0,
5499                x_return_status=> l_return_status,
5500                x_msg_count=> l_msg_count,
5501                x_msg_data=> l_msg_data,
5502                p_app_short_name=> 'OZF', -- need to be resolved , wether it is AMS or OZF
5503                p_dequeue_mode  => DBMS_AQ.REMOVE_NODATA,
5504                p_navigation   => DBMS_AQ.FIRST_MESSAGE,
5505                x_no_more_messages=> l_no_more_messages,
5506                x_header_rec=> l_header_rec,
5507                x_old_header_rec=> l_old_header_rec,
5508                x_header_adj_tbl=> l_header_adj_tbl,
5509                x_old_header_adj_tbl=> l_old_header_adj_tbl,
5510                x_header_price_att_tbl=> l_header_price_att_tbl,
5511                x_old_header_price_att_tbl=> l_old_header_price_att_tbl,
5512                x_header_adj_att_tbl=> l_header_adj_att_tbl,
5513                x_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
5514                x_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
5515                x_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
5516                x_header_scredit_tbl=> l_header_scredit_tbl,
5517                x_old_header_scredit_tbl=> l_old_header_scredit_tbl,
5518                x_line_tbl=> l_line_tbl,
5519                x_old_line_tbl=> l_old_line_tbl,
5520                x_line_adj_tbl=> l_line_adj_tbl,
5521                x_old_line_adj_tbl=> l_old_line_adj_tbl,
5522                x_line_price_att_tbl=> l_line_price_att_tbl,
5523                x_old_line_price_att_tbl=> l_old_line_price_att_tbl,
5524                x_line_adj_att_tbl=> l_line_adj_att_tbl,
5525                x_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
5526                x_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
5527                x_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
5528                x_line_scredit_tbl=> l_line_scredit_tbl,
5529                x_old_line_scredit_tbl=> l_old_line_scredit_tbl,
5530                x_lot_serial_tbl=> l_lot_serial_tbl,
5531                x_old_lot_serial_tbl=> l_old_lot_serial_tbl,
5532                x_action_request_tbl=> l_action_request_tbl
5533             );
5534 
5535             --added for bug 8435487
5536             IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
5537                IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
5538                   fnd_message.set_name ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK_FAIL');
5539                   fnd_msg_pub.ADD;
5540                END IF;
5541                   ozf_utility_pvt.write_conc_log('again exception happened');
5542                RETURN;
5543             ELSE
5544                 l_navigation := DBMS_AQ.FIRST_MESSAGE ;
5545                 COMMIT;
5546                 x_retcode                  := 0;
5547             END IF;
5548          ELSE
5549             ozf_utility_pvt.write_conc_log;
5550             FND_MSG_PUB.INITIALIZE;
5551          END IF;
5552          EXCEPTION
5553          WHEN FND_API.G_EXC_ERROR THEN
5554             ROLLBACK TO get_excep_loop_savepoint;
5555             ozf_utility_pvt.write_conc_log('FALIED');
5556             ozf_utility_pvt.write_conc_log;
5557 
5558         WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
5559             ROLLBACK TO get_excep_loop_savepoint;
5560             ozf_utility_pvt.write_conc_log('FALIED');
5561             ozf_utility_pvt.write_conc_log;
5562 
5563         WHEN OTHERS THEN
5564             ROLLBACK TO get_excep_loop_savepoint;
5565             ozf_utility_pvt.write_conc_log('FAILED');
5566             IF FND_MSG_PUB.Check_Msg_level (FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW) THEN
5567                FND_MESSAGE.Set_Name('OZF','OZF_API_DEBUG_MESSAGE');
5568                FND_MESSAGE.Set_Token('TEXT',sqlerrm);
5569                FND_MSG_PUB.Add;
5570             END IF;
5571             ozf_utility_pvt.write_conc_log;
5572          END;
5573       END LOOP exception_loop;
5574    EXCEPTION
5575       WHEN fnd_api.g_exc_error THEN
5576          x_retcode                  := 1;
5577       WHEN fnd_api.g_exc_unexpected_error THEN
5578          x_retcode                  := 1;
5579       WHEN OTHERS THEN
5580          x_retcode                  := 1;
5581    END get_exception_message;
5582 
5583 
5584    PROCEDURE reprocess_failed_gl_posting (x_errbuf  OUT NOCOPY VARCHAR2,
5585                                           x_retcode OUT NOCOPY NUMBER);
5586    PROCEDURE post_offinvoice_to_gl(x_errbuf  OUT NOCOPY VARCHAR2,
5587                                    x_retcode OUT NOCOPY NUMBER);
5588 
5589 ------------------------------------------------------------------------------
5590 -- Procedure Name
5591 --   Accrue_offers
5592 -- Purpose
5593 --   This procedure performs accruals for all offers for the folow
5594 --   1) Order Managemnt Accruals
5595 --   2) Backdating Adjustment
5596 --   3) Volume Offer Backdating
5597 --   4) reprocess all utilizations whose postings to GL have failed
5598 -- History
5599 --   7/22/2002  mpande Created
5600 --   03/19/2003 yzhao  added parameter p_run_unposted_gl to post unposted accruals to GL
5601 --                       'N' do not process failed GL postings  -- DEFAULT
5602 --                       'Y' reprocess all failed GL postings
5603 ------------------------------------------------------------------------------
5604    PROCEDURE Accrue_offers (x_errbuf OUT NOCOPY VARCHAR2,
5605                             x_retcode OUT NOCOPY NUMBER,
5606                             p_run_exception IN VARCHAR2 := 'N',
5607                             p_run_backdated_adjustment IN VARCHAR2 := 'N',
5608                             p_run_volume_off_adjustment IN VARCHAR2 := 'N',
5609                             p_run_unposted_gl IN VARCHAR2 := 'N',
5610                             p_process_message_count IN NUMBER, --added for bug 8435487
5611                             p_debug IN VARCHAR2    := 'N' )    IS
5612 
5613 l_budget_data       CLOB;
5614 l_offer_data        CLOB;
5615 l_item_key          VARCHAR2(50);
5616 l_event_name        VARCHAR2(80);
5617 l_parameter_list    wf_parameter_list_t;
5618 
5619    BEGIN
5620      g_debug_flag := p_debug;
5621      g_message_count := NVL(p_process_message_count,-1);
5622      G_FAE_START_DATE := TRUNC(sysdate);
5623 
5624      ozf_utility_pvt.write_conc_log (' <===> ORDER MANAGEMENT ACCRUALS BEGIN  <===>');
5625      ozf_utility_pvt.write_conc_log (' <===> g_message_count <===>'||g_message_count);
5626 
5627      ozf_utility_pvt.write_conc_log ('<====ORDER MANAGEMENT ACCRUALS BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5628 
5629      get_message( x_errbuf,
5630                   x_retcode,
5631                   p_run_exception,
5632                   p_debug );
5633 
5634      ozf_utility_pvt.write_conc_log ('<====ORDER MANAGEMENT ACCRUALS END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5635 
5636      ozf_utility_pvt.write_conc_log (' x_retcode '||x_retcode||'x_errbuf'||x_errbuf);
5637 
5638      ozf_utility_pvt.write_conc_log ('<===> ORDER MANAGEMENT ACCRUALS END  <===>');
5639 
5640      IF p_run_backdated_adjustment = 'Y' OR p_run_volume_off_adjustment = 'Y' THEN
5641         ozf_utility_pvt.write_conc_log ('<===> BACKDATED ADJUSTMENT BEGIN  <===>');
5642         ozf_utility_pvt.write_conc_log ('<====BACKDATED ADJUSTMENT BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5643 
5644      -- start backdated Adjustment only
5645         ozf_adjustment_ext_pvt.adjust_backdated_offer(
5646                          x_errbuf,
5647                          x_retcode,
5648                          p_debug );
5649         ozf_utility_pvt.write_conc_log ('<====BACKDATED ADJUSTMENT END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5650 
5651         ozf_utility_pvt.write_conc_log (' BACKDATE ADJUSTMENT x_retcode '||x_retcode||'x_errbuf'||x_errbuf);
5652 
5653         ozf_utility_pvt.write_conc_log ('<===> BACKDATED ADJUSTMENT END <===> ');
5654 
5655      END IF;
5656 
5657      ozf_utility_pvt.write_conc_log ('<===> POST OFFINVOICE UTILIZATION TO GL BEGIN  <===>');
5658      ozf_utility_pvt.write_conc_log ('<====POST OFFINVOICE UTILIZATION TO GL BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5659 
5660      post_offinvoice_to_gl(x_errbuf, x_retcode);
5661 
5662      ozf_utility_pvt.write_conc_log ('<====POST OFFINVOICE UTILIZATION TO GL END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5663      ozf_utility_pvt.write_conc_log ('<===> POST OFFINVOICE UTILIZATION TO GL END  <===>');
5664 
5665      IF p_run_volume_off_adjustment = 'Y' THEN
5666         ozf_utility_pvt.write_conc_log ('<===> VOLUME OFFER ADJUSTMENT BEGIN <=== >');
5667         ozf_utility_pvt.write_conc_log ('<====VOLUME OFFER ADJUSTMENT BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5668 
5669         ozf_adjustment_ext_pvt.adjust_volume_offer(
5670                          x_errbuf,
5671                          x_retcode,
5672                          p_debug);
5673        ozf_utility_pvt.write_conc_log ('<====VOLUME OFFER ADJUSTMENT END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5674        ozf_utility_pvt.write_conc_log (' x_retcode '||x_retcode||'x_errbuf'||x_errbuf);
5675 
5676         ozf_utility_pvt.write_conc_log ('<===> VOLUME OFFER ADJUSTMENT END  <===>');
5677      END IF;
5678 
5679      IF p_run_unposted_gl = 'Y' THEN
5680         ozf_utility_pvt.write_conc_log ('<===> REPROCESS ALL FAILED GL POSTING BEGIN <=== >');
5681         ozf_utility_pvt.write_conc_log ('<====REPROCESS ALL FAILED GL POSTING BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5682 
5683         reprocess_failed_gl_posting(
5684                          x_errbuf,
5685                          x_retcode);
5686         ozf_utility_pvt.write_conc_log ('<====REPROCESS ALL FAILED GL POSTING END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
5687 
5688         ozf_utility_pvt.write_conc_log (' REPROCESS_FAILED_GL_POSTING x_retcode='||x_retcode||' x_errbuf='||x_errbuf);
5689         ozf_utility_pvt.write_conc_log ('<===> REPROCESS ALL FAILED GL POSTING END  <===>');
5690 
5691      END IF;
5692 
5693       --//13333298
5694     ozf_utility_pvt.write_conc_log ('<===> g_tpm_process_enabled  <===>'||g_tpm_process_enabled);
5695 
5696      IF G_TPM_PROCESS_ENABLED = 'Y' THEN
5697      --raise business events
5698         l_item_key := 'ACCRUAL_INFO' || TO_CHAR(SYSDATE,'DDMMRRRRHH24MISS');
5699         l_parameter_list := WF_PARAMETER_LIST_T();
5700 
5701 
5702         l_budget_data := DBMS_XMLGEN.getXml('SELECT ''FUND'' AccrualType,
5703                                                     util.utilization_id UtilizationId,
5704                                                     util.fund_id FundId,
5705                                                     NVL(map.xref_line_id_value,oe.list_line_id) DiscountLineId,
5706                                                     util.product_id ProductId,
5707                                                     util.object_id OrderId,
5708                                                     util.order_line_id OrderLineId,
5709                                                     NVL(line.invoiced_quantity, NVL(line.shipped_quantity, 0)) ShippedQuantity,
5710                                                     (NVL(line.invoiced_quantity, NVL(line.shipped_quantity, 0))*line.unit_selling_price) Revenue,
5711                                                     NVL(util.plan_curr_amount,0) AccrualAmount
5712                                              FROM   oe_order_lines_all line, ozf_funds_utilized_all_b util,
5713                                                     ozf_offers off, oe_price_adjustments oe,
5714                                                     ozf_xref_map map
5715                                              WHERE  line.line_id = util.order_line_id
5716                                                AND  line.header_id = util.object_id
5717                                                AND  util.object_type = ''ORDER''
5718                                                AND  util.request_id = fnd_global.conc_request_id
5719                                                AND  util.plan_type = ''OFFR''
5720                                                AND  util.plan_id = off.qp_list_header_id
5721                                                AND  util.price_adjustment_id = oe.price_adjustment_id
5722                                                AND  util.gl_posted_flag IN (''Y'', ''X'')
5723                                                AND  oe.list_line_id = map.list_line_id(+)
5724                                                AND  NVL(line.invoiced_quantity, NVL(line.shipped_quantity, 0)) <> 0
5725                                                AND  NVL(off.budget_offer_yn, ''N'') = ''Y''', 0);
5726 
5727 
5728         l_offer_data := DBMS_XMLGEN.getXml('SELECT ''OFFR'' AccrualType,
5729                                                    util.utilization_id UtilizationId,
5730                                                    util.plan_id PromotionId,
5731                                                    util.fund_id FundId,
5732                                                    NVL(map.xref_line_id_value,oe.list_line_id) DiscountLineId,
5733                                                    util.product_id ProductId,
5734                                                    util.object_id OrderId,
5735                                                    util.order_line_id OrderLineId,
5736                                                    util.cust_account_id CustomerId,
5737                                                    NVL(line.invoiced_quantity, NVL(line.shipped_quantity, 0)) ShippedQuantity,
5738                                                    (NVL(line.invoiced_quantity, NVL(line.shipped_quantity, 0))*line.unit_selling_price) Revenue,
5739                                                    NVL(util.plan_curr_amount,0) AccrualAmount
5740                                             FROM   oe_order_lines_all line, ozf_funds_utilized_all_b util,
5741                                                    ozf_offers off, oe_price_adjustments oe,
5742                                                    ozf_xref_map map
5743                                             WHERE  line.line_id = util.order_line_id
5744                                               AND  line.header_id = util.object_id
5745                                               AND  util.object_type = ''ORDER''
5746                                               AND  util.request_id = fnd_global.conc_request_id
5747                                               AND  util.price_adjustment_id = oe.price_adjustment_id
5748                                               AND  util.plan_type = ''OFFR''
5749                                               AND  util.plan_id = off.qp_list_header_id
5750                                               AND  util.price_adjustment_id = oe.price_adjustment_id
5751                                               AND  util.gl_posted_flag = ''Y''
5752                                               AND  NVL(line.invoiced_quantity, NVL(line.shipped_quantity, 0)) <> 0
5753                                               AND  oe.list_line_id = map.list_line_id(+)
5754                                               AND  NVL(off.budget_offer_yn, ''N'') = ''N''', 0);
5755 
5756         l_event_name :=  'oracle.apps.ozf.order.accrual.info';
5757 
5758         wf_event.raise(p_event_name => l_event_name,
5759                        p_event_key  => l_item_key,
5760                        p_event_data => l_budget_data,
5761                        p_parameters => l_parameter_list,
5762                        p_send_date  => sysdate);
5763 
5764         wf_event.raise(p_event_name => l_event_name,
5765                        p_event_key  => l_item_key,
5766                        p_event_data => l_offer_data,
5767                        p_parameters => l_parameter_list,
5768                        p_send_date  => sysdate);
5769 
5770      END IF;
5771 
5772 
5773      G_FAE_START_DATE := NULL;
5774    END Accrue_offers;
5775 
5776 
5777 ------------------------------------------------------------------------------
5778 -- Procedure Name
5779 --   post_accrual_to_gl
5780 -- Purpose
5781 --   This procedure posts accrual to GL
5782 -- History
5783 --   03/19/2003  Ying Zhao Created
5784 ------------------------------------------------------------------------------
5785    PROCEDURE post_accrual_to_gl(
5786       p_util_utilization_id         IN              NUMBER,
5787       p_util_object_version_number  IN              NUMBER,
5788       p_util_amount                 IN              NUMBER,
5789       p_util_plan_type              IN              VARCHAR2,
5790       p_util_plan_id                IN              NUMBER,
5791       p_util_plan_amount            IN              NUMBER,
5792       p_util_utilization_type       IN              VARCHAR2,
5793       p_util_fund_id                IN              NUMBER,
5794       p_util_acctd_amount           IN              NUMBER,
5795       p_adjust_paid_flag            IN              BOOLEAN  := false,
5796       p_util_org_id                 IN              NUMBER := NULL,
5797       x_gl_posted_flag              OUT NOCOPY      VARCHAR2,
5798       x_return_status               OUT NOCOPY      VARCHAR2,
5799       x_msg_count                   OUT NOCOPY      NUMBER,
5800       x_msg_data                    OUT NOCOPY      VARCHAR2
5801      )
5802    IS
5803      l_gl_posted_flag               VARCHAR2(1) := G_GL_FLAG_NO;
5804      l_event_id                     NUMBER;
5805      l_return_status                VARCHAR2(1);
5806      l_tmp_number                   NUMBER;
5807      l_acctd_amt                    NUMBER;
5808      l_paid_amt                     NUMBER;
5809      l_rollup_paid_amt              NUMBER;
5810      l_new_univ_amt                 NUMBER;
5811      l_currency_code                VARCHAR2(30);
5812      -- l_mc_col_8                     NUMBER;
5813      l_parent_fund_id               NUMBER;
5814      -- l_mc_record_id                 NUMBER;
5815      l_obj_num                      NUMBER;
5816      l_rate                         NUMBER;
5817      l_objfundsum_rec               ozf_objfundsum_pvt.objfundsum_rec_type := NULL;
5818      l_event_type_code              VARCHAR2(30);
5819      l_adjustment_type              VARCHAR2(1);
5820      l_orig_amt                     NUMBER;
5821      l_rollup_orig_amt              NUMBER;
5822      l_off_invoice_gl_post_flag    VARCHAR2(1);
5823      l_earned_amt  NUMBER;
5824      l_rollup_earned_amt  NUMBER;
5825      l_liability_flag     VARCHAR2(1);
5826      l_accrual_basis   VARCHAR2(30);
5827      l_exchange_rate_type          VARCHAR2(30) := FND_API.G_MISS_CHAR; --nirprasa
5828 
5829      --//Bugfix : 10037158
5830      l_offer_type      varchar2(30);
5831 
5832      CURSOR c_get_offer_type(p_util_id IN NUMBER) IS
5833         SELECT offer_type
5834         FROM ozf_offers a, ozf_funds_utilized_all_b b
5835         WHERE a.qp_list_header_id = b.plan_id
5836           AND b.utilization_id = p_util_id ;
5837 
5838       --nirprasa, added for bug 7030415.
5839      CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
5840         SELECT exchange_rate_type
5841         FROM   ozf_sys_parameters_all
5842         WHERE  org_id = p_org_id;
5843 
5844      CURSOR c_get_fund (p_fund_id IN NUMBER) IS
5845        SELECT  object_version_number, parent_fund_id, currency_code_tc,liability_flag,accrual_basis
5846        FROM    ozf_funds_all_b
5847        WHERE   fund_id = p_fund_id;
5848 
5849      /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
5850      CURSOR c_mc_trans(p_fund_id IN NUMBER) IS
5851          SELECT mc_record_id
5852                ,object_version_number
5853          FROM ozf_mc_transactions_all
5854          WHERE source_object_name ='FUND'
5855          AND source_object_id = p_fund_id;
5856       */
5857 
5858      CURSOR c_parent (p_fund_id IN NUMBER)IS
5859         SELECT fund_id
5860               ,object_version_number
5861         FROM ozf_funds_all_b
5862         connect by prior  parent_fund_id =fund_id
5863         start with fund_id =  p_fund_id;
5864 
5865      -- rimehrot: for R12 update ozf_object_fund_summary table
5866      CURSOR c_get_objfundsum_rec(p_object_type IN VARCHAR2, p_object_id IN NUMBER, p_fund_id IN NUMBER) IS
5867          SELECT objfundsum_id
5868               , object_version_number
5869               , earned_amt
5870               , paid_amt
5871               , plan_curr_earned_amt
5872               , plan_curr_paid_amt
5873               , univ_curr_earned_amt
5874               , univ_curr_paid_amt
5875         FROM   ozf_object_fund_summary
5876         WHERE  object_type = p_object_type
5877         AND    object_id = p_object_id
5878         AND    fund_id = p_fund_id;
5879 
5880       CURSOR c_offinv_flag(p_org_id IN NUMBER) IS
5881         SELECT  NVL(sob.gl_acct_for_offinv_flag, 'F')
5882         FROM    ozf_sys_parameters_all sob
5883         WHERE   sob.org_id = p_org_id;
5884 
5885    BEGIN
5886      SAVEPOINT  post_accrual_to_gl_sp;
5887 
5888       IF g_debug_flag = 'Y' THEN
5889          ozf_utility_pvt.write_conc_log ('    D: post_accrual_to_gl() BEGIN posting to GL for utilization id ' ||
5890                      p_util_utilization_id ||
5891                      ' object_version_number=' || p_util_object_version_number ||
5892                      ' amount=' || p_util_amount ||
5893                      ' plan_type=' || p_util_plan_type ||
5894                      ' utilization_type=' || p_util_utilization_type ||
5895                      ' util_fund_id=' || p_util_fund_id ||
5896                      ' acctd_amount=' || p_util_acctd_amount
5897                      );
5898       END IF;
5899 
5900      IF p_util_plan_type IN ( 'OFFR' , 'PRIC')  THEN         -- yzhao: 10/20/2003 PRICE_LIST is changed to PRIC
5901         -- moved from  IF  l_gl_posted_flag IN(G_GL_FLAG_YES,G_GL_FLAG_NULL,G_GL_FLAG_NOLIAB) THEN
5902         -- to fix bug 5128552
5903         OPEN c_get_fund(p_util_fund_id);
5904         FETCH c_get_fund INTO l_obj_num, l_parent_fund_id, l_currency_code, l_liability_flag,l_accrual_basis;
5905         CLOSE c_get_fund;
5906 
5907         -- yzhao: 11/25/2003 11.5.10 post gl for off invoice discount
5908          IF p_util_utilization_type IN ('ACCRUAL', 'LEAD_ACCRUAL', 'ADJUSTMENT', 'LEAD_ADJUSTMENT', 'UTILIZED','SALES_ACCRUAL') THEN
5909            IF  p_util_utilization_type IN ('ACCRUAL', 'LEAD_ACCRUAL') THEN
5910                --//ER 9382547
5911                --l_event_type_code := 'ACCRUAL';
5912                l_event_type_code := 'ACCRUAL_CREATION';
5913 
5914               IF l_accrual_basis = 'CUSTOMER' AND NVL(l_liability_flag,'N')= 'N' THEN
5915                  l_gl_posted_flag := G_GL_FLAG_NOLIAB;
5916               END IF;
5917            ELSIF p_util_utilization_type = 'UTILIZED' THEN
5918               OPEN c_offinv_flag(p_util_org_id);
5919               FETCH c_offinv_flag INTO l_off_invoice_gl_post_flag;
5920               CLOSE c_offinv_flag;
5921 
5922               --//Bug fix : 10037158
5923               OPEN c_get_offer_type(p_util_utilization_id);
5924               FETCH c_get_offer_type INTO l_offer_type;
5925               CLOSE c_get_offer_type;
5926 
5927               IF l_off_invoice_gl_post_flag = 'F' OR l_offer_type = 'TERMS' THEN
5928                  l_gl_posted_flag := G_GL_FLAG_NULL;
5929               ELSE
5930                  --l_event_type_code := 'OFF_INVOICE';
5931                  l_event_type_code := 'INVOICE_DISCOUNT';
5932               END IF;
5933            ELSIF p_util_utilization_type = 'SALES_ACCRUAL' THEN
5934               l_gl_posted_flag := G_GL_FLAG_NOLIAB;
5935            ELSE
5936              --Adjustments
5937               l_event_type_code   := 'ACCRUAL_ADJUSTMENT';
5938            END IF;
5939 
5940            --//ER 9382547
5941            /*
5942            IF NVL(p_util_amount,0) >= 0 THEN
5943               l_adjustment_type   := 'P'; -- positive
5944            ELSE
5945               l_adjustment_type   := 'N'; -- negetive adjustment
5946            END IF;
5947            */
5948 
5949           IF  l_gl_posted_flag = G_GL_FLAG_NO THEN
5950              OZF_GL_INTERFACE_PVT.Post_Accrual_To_GL (
5951                 p_api_version       => 1.0
5952                ,p_init_msg_list     => fnd_api.g_false
5953                ,p_commit            => fnd_api.g_false
5954                ,p_validation_level  => fnd_api.g_valid_level_full
5955 
5956                ,p_utilization_id    =>  p_util_utilization_id
5957                ,p_event_type_code   => l_event_type_code
5958 
5959                ,x_return_status     => l_return_status
5960                ,x_msg_data          => x_msg_data
5961                ,x_msg_count         => x_msg_count
5962              );
5963 
5964              IF g_debug_flag = 'Y' THEN
5965                 ozf_utility_pvt.write_conc_log ('   D: post_accrual_to_gl() create_gl_entry for utilization id '
5966                                    || p_util_utilization_id || ' returns ' || l_return_status);
5967              END IF;
5968 
5969              IF l_return_status = fnd_api.g_ret_sts_success THEN
5970                 l_gl_posted_flag := G_GL_FLAG_YES;  -- 'Y';
5971              ELSE
5972               -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
5973                 l_gl_posted_flag := G_GL_FLAG_FAIL;  -- 'F';
5974               -- 07/17/2003 yzhao: log error message
5975                 fnd_msg_pub.count_and_get (
5976                     p_count    => x_msg_count,
5977                     p_data     => x_msg_data,
5978                     p_encoded  => fnd_api.g_false
5979                  );
5980                 ozf_utility_pvt.write_conc_log('   /****** Failed to post to GL ******/ for utilization id ' || p_util_utilization_id);
5981 
5982                 ozf_utility_pvt.write_conc_log;
5983                 fnd_msg_pub.initialize;
5984               END IF;
5985 
5986            END IF; --l_gl_posted_flag = G_GL_FLAG_NO
5987 
5988            -- update utilization gl_posted_flag directly to avoid all validations
5989 	   --ninarasi fix for bug 16029659. Set exchange_rate_date to gl_date since exchange_rate_date has to be same as the shipment date.
5990            UPDATE ozf_funds_utilized_all_b
5991            SET last_update_date = SYSDATE
5992                 , last_updated_by = NVL (fnd_global.user_id, -1)
5993                 , last_update_login = NVL (fnd_global.conc_login_id, -1)
5994                 , object_version_number = p_util_object_version_number + 1
5995                 , gl_posted_flag = l_gl_posted_flag
5996 		, exchange_rate_date = gl_date
5997                 --, gl_date = sysdate
5998             WHERE utilization_id = p_util_utilization_id
5999             AND   object_version_number = p_util_object_version_number;
6000 
6001             IF  l_gl_posted_flag IN(G_GL_FLAG_YES,G_GL_FLAG_NULL,G_GL_FLAG_NOLIAB) THEN
6002 
6003               IF g_universal_currency IS NULL THEN
6004                  IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error) THEN
6005                     fnd_message.set_name('OZF', 'OZF_UNIV_CURR_NOT_FOUND');
6006                      fnd_msg_pub.add;
6007                   END IF;
6008                   RAISE fnd_api.g_exc_error;
6009               END IF;
6010 
6011               --Added for bug 7030415
6012                 OPEN c_get_conversion_type(p_util_org_id);
6013                 FETCH c_get_conversion_type INTO l_exchange_rate_type;
6014                 CLOSE c_get_conversion_type;
6015 
6016                 IF g_debug_flag = 'Y' THEN
6017                         ozf_utility_pvt.write_conc_log('**************************START****************************');
6018                         ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' From Amount p_util_amount: '||p_util_amount );
6019                         ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' From Curr l_currency_code: '||l_currency_code );
6020                         ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' To Curr g_universal_currency: '|| g_universal_currency);
6021                         --ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' l_exchange_rate_type: '|| l_exchange_rate_type);
6022                 END IF;
6023 
6024               ozf_utility_pvt.convert_currency(
6025                     x_return_status => l_return_status
6026                     ,p_from_currency => l_currency_code
6027                     ,p_to_currency => g_universal_currency
6028                     ,p_conv_type   => l_exchange_rate_type
6029                     ,p_from_amount => p_util_amount
6030                     ,x_to_amount => l_new_univ_amt
6031                     ,x_rate => l_rate);
6032 
6033               IF g_debug_flag = 'Y' THEN
6034                 ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' Converted Amount l_new_univ_amt: '|| l_new_univ_amt);
6035                 ozf_utility_pvt.write_conc_log('Utilization amount is converted from fund curr to universal curr');
6036                 ozf_utility_pvt.write_conc_log('***************************END******************************');
6037               END IF;
6038 
6039               IF l_return_status = fnd_api.g_ret_sts_error THEN
6040                  RAISE fnd_api.g_exc_error;
6041               ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
6042                  RAISE fnd_api.g_exc_unexpected_error;
6043               END IF;
6044 
6045               IF l_gl_posted_flag = G_GL_FLAG_NOLIAB THEN
6046                  l_orig_amt := p_util_amount;
6047                  l_rollup_orig_amt := l_new_univ_amt;
6048               ELSE
6049                 -- rimehrot changed for R12, Populate new table ozf_object_fund_summary
6050                  l_objfundsum_rec := NULL;
6051                  OPEN c_get_objfundsum_rec(p_util_plan_type
6052                                      , p_util_plan_id
6053                                      , p_util_fund_id);
6054                  FETCH c_get_objfundsum_rec INTO l_objfundsum_rec.objfundsum_id
6055                                            , l_objfundsum_rec.object_version_number
6056                                            , l_objfundsum_rec.earned_amt
6057                                            , l_objfundsum_rec.paid_amt
6058                                            , l_objfundsum_rec.plan_curr_earned_amt
6059                                            , l_objfundsum_rec.plan_curr_paid_amt
6060                                            , l_objfundsum_rec.univ_curr_earned_amt
6061                                            , l_objfundsum_rec.univ_curr_paid_amt;
6062                  CLOSE c_get_objfundsum_rec;
6063 
6064               -- yzhao: 11/25/2003  11.5.10 need to update budget earned amount for accrual, earned and paid amount for off-invoice discount
6065                  IF p_util_utilization_type = 'UTILIZED' OR p_adjust_paid_flag THEN
6066                     l_paid_amt := p_util_amount;
6067                     l_rollup_paid_amt := l_new_univ_amt;
6068                    -- l_mc_col_8 := l_acctd_amt;
6069 
6070                     l_objfundsum_rec.paid_amt := NVL(l_objfundsum_rec.paid_amt, 0) + NVL(l_paid_amt, 0);
6071                     l_objfundsum_rec.plan_curr_paid_amt := NVL(l_objfundsum_rec.plan_curr_paid_amt, 0)
6072                                                                   + NVL(p_util_plan_amount, 0);
6073                     l_objfundsum_rec.univ_curr_paid_amt := NVL(l_objfundsum_rec.univ_curr_paid_amt, 0)
6074                                                                   + NVL(l_rollup_paid_amt, 0);
6075                  END IF;
6076 
6077                  l_earned_amt := p_util_amount;
6078                  l_rollup_earned_amt := l_new_univ_amt;
6079 
6080               -- rimehrot: for R12, populate paid/earned columns in ozf_object_fund_summary
6081               ozf_utility_pvt.write_conc_log('l_objfundsum_rec.earned_amt ' || l_objfundsum_rec.earned_amt);
6082               ozf_utility_pvt.write_conc_log('p_util_amount ' || p_util_amount);
6083               ozf_utility_pvt.write_conc_log('l_objfundsum_rec.plan_curr_earned_amt ' || l_objfundsum_rec.plan_curr_earned_amt);
6084               ozf_utility_pvt.write_conc_log('p_util_plan_amount ' || p_util_plan_amount);
6085               ozf_utility_pvt.write_conc_log('l_objfundsum_rec.univ_curr_earned_amt ' || l_objfundsum_rec.univ_curr_earned_amt);
6086               ozf_utility_pvt.write_conc_log('l_new_univ_amt ' || l_new_univ_amt);
6087                  l_objfundsum_rec.earned_amt := NVL(l_objfundsum_rec.earned_amt, 0) + NVL(p_util_amount, 0);
6088                  l_objfundsum_rec.plan_curr_earned_amt := NVL(l_objfundsum_rec.plan_curr_earned_amt, 0)
6089                                                               + NVL(p_util_plan_amount, 0);
6090                  l_objfundsum_rec.univ_curr_earned_amt := NVL(l_objfundsum_rec.univ_curr_earned_amt, 0)
6091                                                               + NVL(l_new_univ_amt, 0);
6092                  --rimehrot, for R12
6093                  ozf_objfundsum_pvt.update_objfundsum(
6094                        p_api_version                => 1.0,
6095                        p_init_msg_list              => Fnd_Api.G_FALSE,
6096                        p_validation_level           => Fnd_Api.G_VALID_LEVEL_NONE,
6097                        p_objfundsum_rec             => l_objfundsum_rec,
6098                        x_return_status              => l_return_status,
6099                        x_msg_count                  => x_msg_count,
6100                        x_msg_data                   => x_msg_data
6101                     );
6102                  IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
6103                    RAISE fnd_api.g_exc_unexpected_error;
6104                  ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
6105                    RAISE fnd_api.g_exc_error;
6106                  END IF;
6107               -- end R12 changes
6108 
6109               END IF; -- p_util_utilization_type = 'SALES_ACCRUAL'
6110 
6111               UPDATE ozf_funds_all_b
6112               SET    original_budget = NVL(original_budget, 0) + NVL(l_orig_amt, 0)
6113                     ,rollup_original_budget = NVL(rollup_original_budget, 0) + NVL(l_rollup_orig_amt, 0)
6114                     ,earned_amt = NVL(earned_amt, 0) + NVL(l_earned_amt, 0)
6115                     ,paid_amt = NVL(paid_amt, 0 ) + NVL(l_paid_amt, 0)
6116                     ,rollup_earned_amt = NVL(rollup_earned_amt, 0) +  NVL(l_rollup_earned_amt, 0)
6117                     ,rollup_paid_amt = NVL(rollup_paid_amt, 0) + NVL(l_rollup_paid_amt, 0)
6118                     ,object_version_number = l_obj_num + 1
6119               WHERE fund_id =  p_util_fund_id
6120               AND   object_version_number = l_obj_num;
6121 
6122               IF l_parent_fund_id is NOT NULL THEN
6123                  FOR fund IN c_parent(l_parent_fund_id)
6124                  LOOP
6125                       UPDATE ozf_funds_all_b
6126                       SET object_version_number = fund.object_version_number + 1
6127                          ,rollup_earned_amt = NVL(rollup_earned_amt,0) + NVL(l_new_univ_amt,0)
6128                          ,rollup_paid_amt = NVL(rollup_paid_amt,0) + NVL(l_rollup_paid_amt,0)
6129                          ,rollup_original_budget = NVL(rollup_original_budget,0) + NVL(l_rollup_orig_amt,0)
6130                       WHERE fund_id = fund.fund_id
6131                       AND object_version_number = fund.object_version_number;
6132                  END LOOP;
6133               END IF;
6134 
6135 
6136               /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
6137               OPEN c_mc_trans(p_util_fund_id);
6138               FETCH c_mc_trans INTO l_mc_record_id, l_obj_num;
6139               CLOSE c_mc_trans;
6140 
6141               -- update ozf_mc_transaction_all table.
6142               UPDATE ozf_mc_transactions_all
6143                 SET amount_column7 = NVL(amount_column7, 0) + NVL(p_util_acctd_amount,0),
6144                     amount_column8 = NVL(amount_column8, 0) + NVL(l_mc_col_8, 0),
6145                     object_version_number = l_obj_num + 1
6146                 WHERE mc_record_id = l_mc_record_id
6147                 AND object_version_number = l_obj_num;
6148                */
6149           END IF; -- l_gl_posted_flag
6150         END IF; -- for utilization_type
6151      END IF; -- end of plan_type
6152 
6153 
6154      x_gl_posted_flag := l_gl_posted_flag;
6155      x_return_status := fnd_api.g_ret_sts_success;
6156 
6157      IF g_debug_flag = 'Y' THEN
6158         ozf_utility_pvt.write_conc_log ('    D: post_accrual_to_gl() ENDs for utilization id ' || p_util_utilization_id
6159          || ' final gl_posted_flag=' || x_gl_posted_flag);
6160      END IF;
6161 
6162    EXCEPTION
6163      WHEN OTHERS THEN
6164        ROLLBACK TO post_accrual_to_gl_sp;
6165        ozf_utility_pvt.write_conc_log('    D: post_accrual_to_gl(): exception ');
6166        x_return_status            := fnd_api.g_ret_sts_unexp_error;
6167        fnd_msg_pub.count_and_get (
6168             p_count    => x_msg_count,
6169             p_data     => x_msg_data,
6170             p_encoded  => fnd_api.g_false
6171        );
6172    END post_accrual_to_gl;
6173 
6174 
6175 
6176 ------------------------------------------------------------------------------
6177 -- Procedure Name
6178 --   reprocess_failed_gl_posting
6179 -- Purpose
6180 --   This procedure repost to GL for all failed gl postings
6181 -- History
6182 --   03-20-00  yzhao   Created
6183 ------------------------------------------------------------------------------
6184    PROCEDURE reprocess_failed_gl_posting (x_errbuf  OUT NOCOPY VARCHAR2,
6185                                           x_retcode OUT NOCOPY NUMBER
6186                                          ) IS
6187      l_gl_posted_flag          VARCHAR2 (1);
6188      l_return_status           VARCHAR2 (1);
6189      l_msg_count               NUMBER;
6190      l_msg_data                VARCHAR2(2000);
6191 
6192      l_utilIdTbl               utilIdTbl;
6193      l_objVerTbl               objVerTbl;
6194      l_amountTbl               amountTbl;
6195      l_planTypeTbl             planTypeTbl;
6196      l_planIdTbl               planIdTbl;
6197      l_planAmtTbl              planAmtTbl;
6198      l_utilTypeTbl             utilTypeTbl;
6199      l_fundIdTbl               fundIdTbl;
6200      l_acctAmtTbl              acctAmtTbl;
6201      l_orgIdTbl                orgIdTbl;
6202      l_glDateTbl               glDateTbl;
6203      l_objectIdTbl             objectIdTbl;
6204      l_orderLineIdTbl          orderLineIdTbl;
6205 
6206      l_inv_date                DATE;
6207 
6208      CURSOR c_get_failed_gl_posting IS
6209        SELECT utilization_id, object_version_number,
6210               plan_type, utilization_type,
6211               amount, fund_id, acctd_amount, fund_request_amount, plan_id,org_id, gl_date, object_id, order_line_id
6212        FROM   ozf_funds_utilized_all_b
6213        WHERE  plan_type IN ( 'OFFR' , 'PRIC')       -- yzhao: 10/20/2003 PRICE_LIST is changed to PRIC
6214          -- AND  utilization_type = 'ACCRUAL'          yzhao: 01/29/2004 11.5.10 off-invoice offer, LEAD_ACCRUAL may post to GL too
6215          AND  gl_posted_flag = G_GL_FLAG_FAIL;  -- 'F';
6216 
6217      --fix for bug 13824967
6218      CURSOR c_invoice_date(p_headerId IN NUMBER, p_lineId IN NUMBER) IS
6219        SELECT trunc(cust.trx_date)     -- transaction(invoice) date
6220          FROM ra_customer_trx_all cust,
6221               ra_customer_trx_lines_all cust_lines,
6222               oe_order_headers_all oeh
6223         WHERE cust.customer_trx_id = cust_lines.customer_trx_id
6224           AND cust_lines.interface_line_attribute1 = oeh.order_number
6225           AND cust_lines.interface_line_attribute6 = TO_CHAR(p_lineId)
6226           AND cust_lines.interface_line_context = 'ORDER ENTRY'
6227           AND oeh.header_id = p_headerId;
6228 
6229    BEGIN
6230       IF g_debug_flag = 'Y' THEN
6231          ozf_utility_pvt.write_conc_log ('    D: Begin posting to GL for all failed postings');
6232       END IF;
6233 
6234      OPEN c_get_failed_gl_posting;
6235      LOOP
6236          FETCH c_get_failed_gl_posting BULK COLLECT INTO l_utilIdTbl, l_objVerTbl
6237                                                        , l_planTypeTbl, l_utilTypeTbl
6238                                                        , l_amountTbl, l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
6239                                                        , l_glDateTbl, l_objectIdTbl, l_orderLineIdTbl
6240                                                        LIMIT g_bulk_limit;
6241          FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
6242 
6243            --Bug 11670604 - if auto-invoice is not run, then fail gl posting and wait until autoinvoice is run
6244            --to post to GL based on invoice date
6245 
6246            -- Bug 13463758, fix issue for RMA orders, when FAE is run before auto-invoice,
6247            --The failed RMA records were not getting processed. removed condition
6248            --IF NVL(fnd_profile.VALUE ('OZF_ORDER_GLPOST_PHASE'), 'SHIPPED') = 'INVOICED' THEN
6249 
6250              l_inv_date := NULL;
6251              IF l_glDateTbl(i) IS NULL THEN
6252                 --IF NVL(fnd_profile.VALUE ('OZF_ORDER_GLPOST_PHASE'), 'SHIPPED') = 'INVOICED' THEN
6253 
6254 
6255                    OPEN c_invoice_date(l_objectIdTbl(i), l_orderLineIdTbl(i));
6256                    FETCH c_invoice_date INTO l_inv_date;
6257                    CLOSE c_invoice_date;
6258 
6259                    IF g_debug_flag = 'Y' THEN
6260                       ozf_utility_pvt.write_conc_log('kd: Invoice Date l_inv_date: ' || l_inv_date);
6261                       ozf_utility_pvt.write_conc_log('kd: utilization id: ' || l_utilIdTbl(i));
6262                    END IF;
6263                    --l_inv_date := NULL;
6264 
6265                    IF l_inv_date IS NOT NULL THEN
6266                       UPDATE ozf_funds_utilized_all_b
6267                          SET gl_date = l_inv_date
6268                        WHERE utilization_id = l_utilIdTbl(i);
6269                    ELSE
6270                       GOTO l_endofutilloop;
6271                    END IF;
6272                 --END IF;
6273              ELSE
6274                 l_inv_date := l_glDateTbl(i);
6275              END IF;
6276 
6277              IF l_inv_date IS NOT NULL THEN
6278              post_accrual_to_gl( p_util_utilization_id        => l_utilIdTbl(i)
6279                                , p_util_object_version_number => l_objVerTbl(i)
6280                                , p_util_amount                => l_amountTbl(i)
6281                                , p_util_plan_type             => l_planTypeTbl(i)
6282                                , p_util_plan_id               => l_planIdTbl(i)
6283                                , p_util_plan_amount           => l_planAmtTbl(i)
6284                                , p_util_utilization_type      => l_utilTypeTbl(i)
6285                                , p_util_fund_id               => l_fundIdTbl(i)
6286                                , p_util_acctd_amount          => l_acctAmtTbl(i)
6287                                , p_util_org_id                     => l_orgIdTbl(i)
6288                                , x_gl_posted_flag             => l_gl_posted_flag
6289                                , x_return_status              => l_return_status
6290                                , x_msg_count                  => l_msg_count
6291                                , x_msg_data                   => l_msg_data
6292                            );
6293              END IF;
6294 
6295              IF l_return_status <> fnd_api.g_ret_sts_success THEN
6296                 -- failed again. Leave as it is.
6297                 IF g_debug_flag = 'Y' THEN
6298                    ozf_utility_pvt.write_conc_log('   /****** Failed to post to GL ******/ for utilization id ' || l_utilIdTbl(i));
6299                 END IF;
6300              ELSE
6301                 IF g_debug_flag = 'Y' THEN
6302                    ozf_utility_pvt.write_conc_log ('    D: successfully posted to GL for utilization id ' || l_utilIdTbl(i)
6303                                 || '  x_gl_posted_flag=' || l_gl_posted_flag);
6304                 END IF;
6305 
6306                 -- yzhao: 03/04/2004 post gl for related accruals from offer adjustment or object reconcile
6307                 IF l_gl_posted_flag = G_GL_FLAG_YES THEN
6308                     post_related_accrual_to_gl(
6309                         p_utilization_id              => l_utilIdTbl(i)
6310                       , p_utilization_type            => l_utilTypeTbl(i)
6311                       , x_return_status               => l_return_status
6312                       , x_msg_count                   => l_msg_count
6313                       , x_msg_data                    => l_msg_data
6314                   );
6315                 END IF;
6316 
6317              END IF;
6318 
6319              <<l_endofutilloop>>
6320                 NULL;
6321 
6322          END LOOP;  -- FOR i IN NVL(p_utilIdTbl.FIRST, 1) .. NVL(p_utilIdTbl.LAST, 0) LOOP
6323 
6324          EXIT WHEN c_get_failed_gl_posting%NOTFOUND;
6325      END LOOP;  -- bulk fetch loop
6326      CLOSE c_get_failed_gl_posting;
6327 
6328      x_retcode := 0;
6329      IF g_debug_flag = 'Y' THEN
6330         ozf_utility_pvt.write_conc_log ('    D: End successfully posting to GL for all failed postings');
6331      END IF;
6332 
6333    EXCEPTION
6334      WHEN OTHERS THEN
6335        x_retcode                  := 1;
6336        ozf_utility_pvt.write_conc_log('   /****** Failed to post to GL - exception ' ||  sqlcode || ' ******/' );
6337    END reprocess_failed_gl_posting;
6338 
6339 
6340 ------------------------------------------------------------------------------
6341 -- Procedure Name
6342 --   post_offinvoice_to_gl
6343 -- Purpose
6344 --   This procedure posts utilization created by off-invoice offer to GL only when AutoInvoice workflow is done
6345 -- History
6346 --   03/19/2003  Ying Zhao Created
6347 ------------------------------------------------------------------------------
6348   PROCEDURE post_offinvoice_to_gl(
6349              x_errbuf  OUT NOCOPY VARCHAR2,
6350              x_retcode OUT NOCOPY NUMBER     )
6351    IS
6352      l_gl_posted_flag             VARCHAR2(1);
6353      l_invoice_line_id            NUMBER;
6354      l_gl_date                    DATE;
6355      l_return_status              VARCHAR2 (1);
6356      l_msg_count                  NUMBER;
6357      l_msg_data                   VARCHAR2 (2000);
6358      l_order_number               NUMBER;
6359      l_object_id                  NUMBER := 0;
6360 
6361      l_utilIdTbl               utilIdTbl;
6362      l_objVerTbl               objVerTbl;
6363      l_amountTbl               amountTbl;
6364      l_planTypeTbl             planTypeTbl;
6365      l_planIdTbl               planIdTbl;
6366      l_planAmtTbl              planAmtTbl;
6367      l_utilTypeTbl             utilTypeTbl;
6368      l_fundIdTbl               fundIdTbl;
6369      l_acctAmtTbl              acctAmtTbl;
6370      l_orgIdTbl                orgIdTbl;
6371      l_objectIdTbl             objectIdTbl;
6372      l_priceAdjTbl             priceAdjTbl;
6373 
6374      --nirprasa, ER 8399134
6375      l_excDateTbl              excDateTbl;
6376      l_excTypeTbl              excTypeTbl;
6377      l_currCodeTbl             currCodeTbl;
6378      l_planCurrCodeTbl         planCurrCodeTbl;
6379      l_fundReqCurrCodeTbl      fundReqCurrCodeTbl;
6380      l_planCurrAmtTbl          planCurrAmtTbl;
6381      l_planCurrAmtRemTbl       planCurrAmtRemTbl;
6382      l_univCurrAmtTbl          univCurrAmtTbl;
6383      -- yzhao: 03/21/2003 get invoiced order's utilization record, post to GL
6384      --nirprasa, ER 8399134
6385      CURSOR c_get_all_util_rec IS
6386        SELECT utilization_id, object_version_number, plan_type, utilization_type, amount
6387               , fund_id, acctd_amount, fund_request_amount, plan_id
6388               ,org_id, exchange_rate_type, exchange_rate_date
6389               , currency_code, plan_currency_code, fund_request_currency_code
6390               , plan_curr_amount, plan_curr_amount_remaining
6391               , univ_curr_amount,object_id, price_adjustment_id
6392        FROM   ozf_funds_utilized_all_b
6393        WHERE  utilization_type = 'UTILIZED'
6394        AND    gl_posted_flag = 'N'
6395        AND    object_type = 'ORDER'
6396        AND    price_adjustment_id IS NOT NULL;
6397 
6398      -- Replaced Sales_Order Column with interface_line_attribute1 for Bug 8463331
6399      CURSOR c_get_invoice_status(p_price_adjustment_id IN NUMBER, p_order_number IN  VARCHAR2) IS
6400        SELECT customer_trx_line_id, cust.trx_date
6401        FROM   ra_customer_trx_all cust
6402             , ra_customer_trx_lines_all cust_lines
6403             , oe_price_adjustments price
6404        WHERE  price.price_adjustment_id = p_price_adjustment_id
6405        AND    cust_lines.customer_trx_line_id IS NOT NULL
6406        AND    interface_line_context = 'ORDER ENTRY'
6407        AND    cust_lines.interface_line_attribute6 = TO_CHAR(price.line_id)
6408        AND    cust_lines.interface_line_attribute1 = p_order_number -- added for partial index; performance bug fix 3917556
6409        AND    cust.customer_trx_id = cust_lines.customer_trx_id;
6410 
6411 
6412          -- added for 3917556
6413       CURSOR c_get_offer_info (p_header_id IN NUMBER) IS
6414          SELECT order_number
6415            FROM oe_order_headers_all
6416           WHERE header_id = p_header_id;
6417 
6418    BEGIN
6419      x_retcode := 0;
6420      SAVEPOINT  post_offinvoice_to_gl_sp;
6421 
6422      IF g_debug_flag = 'Y' THEN
6423         ozf_utility_pvt.write_conc_log ('    D: post_offinvoice_to_gl() BEGIN ');
6424      END IF;
6425 
6426      OPEN c_get_all_util_rec;
6427      LOOP
6428         FETCH c_get_all_util_rec BULK COLLECT INTO
6429         l_utilIdTbl, l_objVerTbl, l_planTypeTbl, l_utilTypeTbl, l_amountTbl
6430       , l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
6431       , l_excTypeTbl, l_excDateTbl, l_currCodeTbl, l_planCurrCodeTbl
6432       , l_fundReqCurrCodeTbl, l_planCurrAmtTbl, l_planCurrAmtRemTbl
6433       , l_univCurrAmtTbl, l_objectIdTbl ,l_priceAdjTbl
6434        LIMIT g_bulk_limit;
6435 
6436 
6437         IF g_debug_flag = 'Y' THEN
6438            ozf_utility_pvt.write_conc_log ('    D: l_utilIdTbl count: ' || l_utilIdTbl.COUNT);
6439         END IF;
6440 
6441         FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
6442 
6443            IF l_object_id <> l_objectIdTbl(i) THEN
6444               l_object_id := l_objectIdTbl(i);
6445               OPEN c_get_offer_info(l_object_id);
6446               FETCH c_get_offer_info INTO l_order_number;
6447               CLOSE c_get_offer_info;
6448            END IF;
6449 
6450            l_invoice_line_id := NULL; --Bugfix: 7431334
6451 
6452            OPEN c_get_invoice_status(l_priceAdjTbl(i), l_order_number);
6453            FETCH c_get_invoice_status INTO l_invoice_line_id, l_gl_date;
6454            CLOSE c_get_invoice_status;
6455 
6456            IF l_invoice_line_id IS NOT NULL THEN
6457 
6458                -- fix for bug 6998502
6459               IF l_gl_date IS NULL THEN
6460                l_gl_date := sysdate;
6461               END IF;
6462 
6463               --Fix for Bug 12657908
6464               FORALL t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
6465                UPDATE ozf_funds_utilized_all_b
6466                SET gl_date = l_gl_date,
6467                year_id = (select ent_year_id FROM OZF_TIME_ENT_YEAR
6468                                     WHERE l_gl_date between start_date and end_date)
6469                WHERE utilization_id = l_utilIdTbl(t_i);
6470                --nirprasa, ER 8399134
6471                IF TRUNC(l_excDateTbl(i)) <> TRUNC(l_gl_date) AND l_utilTypeTbl(i) IN ('UTILIZED') THEN
6472 
6473                   l_excDateTbl(i) := l_gl_date;
6474 
6475                   IF g_debug_flag = 'Y' THEN
6476                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: start');
6477                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_excDateTbl(t_i) '||l_excDateTbl(i));
6478                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_excTypeTbl(t_i) '||l_excTypeTbl(i));
6479                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_orgIdTbl(t_i) '||l_orgIdTbl(i));
6480                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_currCodeTbl(t_i) '||l_currCodeTbl(i));
6481                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planCurrCodeTbl(t_i) '||l_planCurrCodeTbl(i));
6482                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_fundReqCurrCodeTbl(t_i) '||l_fundReqCurrCodeTbl(i));
6483                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_amountTbl(t_i) '||l_amountTbl(i));
6484                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planCurrAmtTbl(t_i) '||l_planCurrAmtTbl(i));
6485                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planCurrAmtRemTbl(t_i) '||l_planCurrAmtRemTbl(i));
6486                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_univCurrAmtTbl(t_i) '||l_univCurrAmtTbl(i));
6487                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_acctAmtTbl(t_i) '||l_acctAmtTbl(i));
6488                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planIdTbl(t_i) '||l_planIdTbl(i));
6489                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_planTypeTbl(t_i) '||l_planTypeTbl(i));
6490                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_fundIdTbl(t_i) '||l_fundIdTbl(i));
6491                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_utilIdTbl(t_i) '||l_utilIdTbl(i));
6492                      ozf_utility_pvt.write_conc_log(' recalculate_earnings: l_utilTypeTbl(t_i) '||l_utilTypeTbl(i));
6493                   END IF;
6494 
6495                  recalculate_earnings(p_exchange_rate_date     => l_excDateTbl(i),
6496                                       p_exchange_rate_type     => l_excTypeTbl(i),
6497                                       p_util_org_id            => l_orgIdTbl(i),
6498                                       p_currency_code          => l_currCodeTbl(i),
6499                                       p_plan_currency_code     => l_planCurrCodeTbl(i),
6500                                       p_fund_req_currency_code => l_fundReqCurrCodeTbl(i),
6501                                       p_amount                 => l_amountTbl(i),
6502                                       p_plan_curr_amount       => l_planCurrAmtTbl(i),
6503                                       p_plan_curr_amount_rem   => l_planCurrAmtRemTbl(i),
6504                                       p_univ_curr_amount       => l_univCurrAmtTbl(i),
6505                                       p_acctd_amount           => l_acctAmtTbl(i),
6506                                       p_fund_req_amount        => l_planAmtTbl(i),
6507                                       p_util_plan_id           => l_planIdTbl(i),
6508                                       p_util_plan_type         => l_planTypeTbl(i),
6509                                       p_util_fund_id           => l_fundIdTbl(i),
6510                                       p_util_utilization_id    => l_utilIdTbl(i),
6511                                       p_util_utilization_type  => l_utilTypeTbl(i),
6512                                       x_return_status          => l_return_status,
6513                                       x_msg_count              => l_msg_count,
6514                                       x_msg_data               => l_msg_data);
6515                      IF g_debug_flag = 'Y' THEN
6516                         ozf_utility_pvt.write_conc_log(' recalculate_earnings returns ' || l_return_status
6517                              );
6518                      END IF;
6519               END IF;
6520 
6521               post_accrual_to_gl( p_util_utilization_id        => l_utilIdTbl(i)
6522                                , p_util_object_version_number => l_objVerTbl(i)
6523                                , p_util_amount                => l_amountTbl(i)
6524                                , p_util_plan_type             => l_planTypeTbl(i)
6525                                , p_util_plan_id               => l_planIdTbl(i)
6526                                , p_util_plan_amount           => l_planAmtTbl(i)
6527                                , p_util_utilization_type      => 'UTILIZED'
6528                                , p_util_fund_id               => l_fundIdTbl(i)
6529                                , p_util_acctd_amount          => l_acctAmtTbl(i)
6530                                , x_gl_posted_flag             => l_gl_posted_flag
6531                                , x_return_status              => l_return_status
6532                                , x_msg_count                  => l_msg_count
6533                                , x_msg_data                   => l_msg_data
6534                            );
6535 
6536              -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
6537               IF g_debug_flag = 'Y' THEN
6538                  ozf_utility_pvt.write_conc_log ('    D:  post_offinvoice_to_gl() post_accrual_to_gl(util_id='
6539                            || l_utilIdTbl(i)
6540                            || ') returns ' || l_return_status || ' x_gl_posted_flag' || l_gl_posted_flag);
6541               END IF;
6542 
6543              -- yzhao: 03/04/2004 post gl for related accruals from offer adjustment or object reconcile
6544               IF l_return_status = fnd_api.g_ret_sts_success AND l_gl_posted_flag = G_GL_FLAG_YES THEN
6545                  post_related_accrual_to_gl(
6546                       p_utilization_id              => l_utilIdTbl(i)
6547                     , p_utilization_type            => 'UTILIZED'
6548                     , p_gl_date                     => l_gl_date
6549                     , x_return_status               => l_return_status
6550                     , x_msg_count                   => l_msg_count
6551                     , x_msg_data                    => l_msg_data
6552                 );
6553               END IF;
6554            END IF; --l_invoice_line_id IS NOT
6555 
6556         END LOOP;  -- FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
6557 
6558         EXIT WHEN c_get_all_util_rec%NOTFOUND;
6559      END LOOP;   -- bulk fetch
6560      CLOSE c_get_all_util_rec;
6561 
6562      IF g_debug_flag = 'Y' THEN
6563          ozf_utility_pvt.write_conc_log ('    D: post_offinvoice_to_gl() END');
6564      END IF;
6565 
6566 
6567    EXCEPTION
6568      WHEN OTHERS THEN
6569        ROLLBACK TO post_offinvoice_to_gl_sp;
6570        x_retcode := 1;
6571        ozf_utility_pvt.write_conc_log('    D: post_offinvoice_to_gl(): exception ');
6572        fnd_msg_pub.count_and_get (
6573             p_count    => l_msg_count,
6574             p_data     => l_msg_data,
6575             p_encoded  => fnd_api.g_false
6576        );
6577        x_errbuf := l_msg_data;
6578    END post_offinvoice_to_gl;
6579 
6580 ------------------------------------------------------------------------------
6581 -- Procedure Name
6582 --   post_related_accrual_to_gl
6583 -- Purpose
6584 --   This procedure posts utilization(from offer adjustment or offer reconcile) to GL
6585 --        called when the original utilization is posted to GL successfully
6586 -- History
6587 --   03/04/2003  Ying Zhao Created
6588 ------------------------------------------------------------------------------
6589    PROCEDURE post_related_accrual_to_gl(
6590       p_utilization_id              IN              NUMBER,
6591       p_utilization_type            IN              VARCHAR2,
6592       p_gl_date                     IN              DATE      := NULL,
6593       x_return_status               OUT NOCOPY      VARCHAR2,
6594       x_msg_count                   OUT NOCOPY      NUMBER,
6595       x_msg_data                    OUT NOCOPY      VARCHAR2)
6596    IS
6597      l_adjust_paid_flag             BOOLEAN := false;
6598      l_gl_posted_flag               VARCHAR2(1) := NULL;
6599      l_return_status                VARCHAR2 (1);
6600      l_msg_count                    NUMBER;
6601      l_msg_data                     VARCHAR2 (2000);
6602 
6603      l_utilIdTbl                    utilIdTbl;
6604      l_objVerTbl                    objVerTbl;
6605      l_amountTbl                    amountTbl;
6606      l_planTypeTbl                  planTypeTbl;
6607      l_planIdTbl                    planIdTbl;
6608      l_planAmtTbl                   planAmtTbl;
6609      l_utilTypeTbl                  utilTypeTbl;
6610      l_fundIdTbl                    fundIdTbl;
6611      l_acctAmtTbl                   acctAmtTbl;
6612      l_orgIdTbl                     orgIdTbl;
6613      -- yzhao: 03/04/2004 get related accraul records, post to GL
6614      CURSOR c_get_related_accrual IS
6615        SELECT utilization_id, object_version_number, plan_type, utilization_type, amount
6616             , fund_id, acctd_amount, fund_request_amount, plan_id,org_id
6617        FROM   ozf_funds_utilized_all_b
6618        WHERE  gl_posted_flag = G_GL_FLAG_NO  --// OR gl_posted_flag = G_GL_FLAG_FAIL) Commented for Bugfix 13004854
6619        AND    orig_utilization_id = p_utilization_id;
6620 
6621    BEGIN
6622      SAVEPOINT  post_related_accrual_to_gl_sp;
6623      IF g_debug_flag = 'Y' THEN
6624         ozf_utility_pvt.write_conc_log ('    D: post_related_accrual_to_gl() BEGIN posting related accruals to GL for utilization id ' || p_utilization_id);
6625      END IF;
6626 
6627      IF p_utilization_type = 'UTILIZED' THEN
6628         l_adjust_paid_flag := true;
6629      END IF;
6630 
6631      OPEN c_get_related_accrual;
6632      LOOP
6633          FETCH c_get_related_accrual BULK COLLECT
6634          INTO l_utilIdTbl, l_objVerTbl, l_planTypeTbl, l_utilTypeTbl, l_amountTbl
6635             , l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
6636          LIMIT g_bulk_limit;
6637 
6638          -- Fix for Bug 12657908
6639          IF p_gl_date IS NOT NULL THEN
6640              FORALL i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
6641                  UPDATE ozf_funds_utilized_all_b
6642                     SET gl_date = p_gl_date,
6643                     year_id = (select ent_year_id FROM OZF_TIME_ENT_YEAR
6644                                     WHERE p_gl_date between start_date and end_date)
6645                   WHERE utilization_id = l_utilIdTbl(i);
6646          END IF;
6647 
6648          FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
6649              post_accrual_to_gl( p_util_utilization_id        => l_utilIdTbl(i)
6650                                , p_util_object_version_number => l_objVerTbl(i)
6651                                , p_util_amount                => l_amountTbl(i)
6652                                , p_util_plan_type             => l_planTypeTbl(i)
6653                                , p_util_plan_id               => l_planIdTbl(i)
6654                                , p_util_plan_amount           => l_planAmtTbl(i)
6655                                , p_util_utilization_type      => l_utilTypeTbl(i)
6656                                , p_util_fund_id               => l_fundIdTbl(i)
6657                                , p_util_acctd_amount          => l_acctAmtTbl(i)
6658                                , p_adjust_paid_flag           => l_adjust_paid_flag
6659                                , p_util_org_id                => l_orgIdTbl(i)
6660                                , x_gl_posted_flag             => l_gl_posted_flag
6661                                , x_return_status              => l_return_status
6662                                , x_msg_count                  => l_msg_count
6663                                , x_msg_data                   => l_msg_data
6664                            );
6665 
6666             -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
6667             IF g_debug_flag = 'Y' THEN
6668                ozf_utility_pvt.write_conc_log('    D:  post_related_accrual_to_gl() post_accrual_to_gl(util_id=' || l_utilIdTbl(i)
6669                            || ') returns ' || l_return_status || ' x_gl_posted_flag' || l_gl_posted_flag);
6670             END IF;
6671          END LOOP; -- FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
6672 
6673          EXIT WHEN c_get_related_accrual%NOTFOUND;
6674      END LOOP;  -- bulk fetch
6675      CLOSE c_get_related_accrual;
6676 
6677      x_return_status := fnd_api.g_ret_sts_success;
6678      IF g_debug_flag = 'Y' THEN
6679         ozf_utility_pvt.write_conc_log ('    D: post_related_accrual_to_gl() ENDs for utilization id ' || p_utilization_id);
6680      END IF;
6681 
6682    EXCEPTION
6683      WHEN OTHERS THEN
6684        ROLLBACK TO post_related_accrual_to_gl_sp;
6685        ozf_utility_pvt.write_conc_log('    D: post_related_accrual_to_gl(): exception ');
6686        x_return_status            := fnd_api.g_ret_sts_unexp_error;
6687        fnd_msg_pub.count_and_get (
6688             p_count    => x_msg_count,
6689             p_data     => x_msg_data,
6690             p_encoded  => fnd_api.g_false
6691        );
6692 
6693    END post_related_accrual_to_gl;
6694 
6695      ------------------------------------------------------------------------------
6696 -- Procedure Name
6697 --   recalculate_earnings
6698 -- Purpose
6699 --   This procedure re-converts the converted amounts in utilization table
6700 --   gl_date will be used as exchange_date.
6701 --
6702 -- History
6703 -- 04/29/2009 nirprasa Created for ER 8399134
6704 ------------------------------------------------------------------------------
6705    PROCEDURE recalculate_earnings (
6706       p_exchange_rate_date          IN            DATE,
6707       p_exchange_rate_type          IN            VARCHAR2,
6708       p_util_org_id                 IN            NUMBER,
6709       p_currency_code               IN            VARCHAR2,
6710       p_plan_currency_code          IN            VARCHAR2,
6711       p_fund_req_currency_code      IN            VARCHAR2,
6712       p_amount                      IN            NUMBER,
6713       p_plan_curr_amount            IN            NUMBER,
6714       p_plan_curr_amount_rem        IN            NUMBER,
6715       p_univ_curr_amount            IN            NUMBER,
6716       p_acctd_amount                IN            NUMBER,
6717       p_fund_req_amount             IN            NUMBER,
6718       p_util_plan_id                IN            NUMBER,
6719       p_util_plan_type              IN            VARCHAR2,
6720       p_util_fund_id                IN            NUMBER,
6721       p_util_utilization_id         IN            NUMBER,
6722       p_util_utilization_type       IN            VARCHAR2,
6723       x_return_status               OUT NOCOPY    VARCHAR2,
6724       x_msg_count                   OUT NOCOPY    VARCHAR2,
6725       x_msg_data                    OUT NOCOPY    VARCHAR2)
6726    IS
6727 
6728    CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
6729         SELECT exchange_rate_type
6730         FROM   ozf_sys_parameters_all
6731         WHERE  org_id = p_org_id;
6732 
6733    CURSOR c_get_objfundsum_rec(p_object_type IN VARCHAR2, p_object_id IN NUMBER, p_fund_id IN NUMBER) IS
6734         SELECT objfundsum_id
6735               , object_version_number
6736               , utilized_amt
6737               , earned_amt
6738               , paid_amt
6739               , plan_curr_utilized_amt
6740               , plan_curr_earned_amt
6741               , plan_curr_paid_amt
6742               , univ_curr_utilized_amt
6743               , univ_curr_earned_amt
6744               , univ_curr_paid_amt
6745         FROM   ozf_object_fund_summary
6746         WHERE  object_type = p_object_type
6747         AND    object_id = p_object_id
6748         AND    fund_id = p_fund_id;
6749 
6750    CURSOR c_parent (p_fund_id IN NUMBER)IS
6751         SELECT fund_id
6752               ,object_version_number
6753         FROM ozf_funds_all_b
6754         connect by prior  parent_fund_id =fund_id
6755         start with fund_id =  p_fund_id;
6756 
6757    CURSOR c_get_fund (p_fund_id IN NUMBER) IS
6758        SELECT  object_version_number, parent_fund_id,liability_flag,accrual_basis
6759        FROM    ozf_funds_all_b
6760        WHERE   fund_id = p_fund_id;
6761 
6762    CURSOR c_act_budget_rec(p_plan_id IN NUMBER) IS
6763        SELECT activity_budget_id
6764             , object_version_number
6765        FROM   ozf_act_budgets
6766        WHERE  transfer_type = 'UTILIZED'
6767        AND    status_code = 'APPROVED'
6768        AND    act_budget_used_by_id = p_plan_id;
6769 
6770    l_exchange_rate_type         VARCHAR2(30);
6771    l_exchange_rate              NUMBER;
6772    l_rate                       NUMBER;
6773    l_conv_amount                NUMBER;
6774    l_conv_amount_remg           NUMBER;
6775    l_conv_acctd_amount          NUMBER;
6776    l_conv_acctd_amount_remg     NUMBER;
6777    l_conv_fund_req_amount       NUMBER;
6778    l_conv_fund_req_amount_remg  NUMBER;
6779    l_conv_univ_amount           NUMBER;
6780    l_conv_univ_amount_remg      NUMBER;
6781    l_paid_amt                   NUMBER;
6782    l_paid_conv_amt              NUMBER;
6783    l_rollup_paid_amt            NUMBER;
6784    l_rollup_paid_conv_amt       NUMBER;
6785    l_rollup_orig_amt            NUMBER := 0;
6786    l_orig_amt                   NUMBER := 0;
6787    l_act_budget_id              NUMBER;
6788    l_act_budget_objver          NUMBER;
6789    l_order_ledger               NUMBER;
6790    l_obj_num                    NUMBER;
6791    l_parent_fund_id             NUMBER;
6792    l_liability_flag             VARCHAR2(1);
6793    l_accrual_basis              VARCHAR2(30);
6794    l_ord_ledger_name            VARCHAR2(150);
6795    l_sob_type_code              VARCHAR2(30);
6796    l_fc_code                    VARCHAR2(150);
6797    l_msg_count                  NUMBER;
6798    l_return_status              VARCHAR2(30);
6799    l_msg_data                   VARCHAR2(2000);
6800    l_gl_posted_flag             VARCHAR2(1);
6801    p_adjust_paid_flag           BOOLEAN  := false;
6802    l_objfundsum_rec             ozf_objfundsum_pvt.objfundsum_rec_type := NULL;
6803 
6804    BEGIN
6805      SAVEPOINT  recalculate_earnings_sp;
6806      IF g_debug_flag = 'Y' THEN
6807         ozf_utility_pvt.write_conc_log ('recalculate_earnings_sp() BEGIN converting amounts based on shipping date for utilization id ' || p_util_utilization_id);
6808      END IF;
6809 
6810      OPEN c_get_conversion_type(p_util_org_id);
6811      FETCH c_get_conversion_type INTO l_exchange_rate_type;
6812      CLOSE c_get_conversion_type;
6813 
6814      --budget
6815      IF p_currency_code = p_plan_currency_code THEN
6816         l_conv_amount := p_plan_curr_amount;
6817      ELSE
6818      ozf_utility_pvt.convert_currency (
6819                x_return_status => l_return_status,
6820                p_from_currency => p_plan_currency_code,
6821                p_to_currency   => p_currency_code,
6822                p_conv_type     => l_exchange_rate_type,
6823                p_conv_date     => p_exchange_rate_date,
6824                p_from_amount   => p_plan_curr_amount,
6825                x_to_amount     => l_conv_amount,
6826                x_rate          => l_rate
6827               );
6828      END IF;
6829 
6830      IF NVL(p_plan_curr_amount_rem,0) <> 0 THEN
6831         l_conv_amount_remg := l_conv_amount;
6832      END IF;
6833 
6834      --functional
6835      --get the order's ledger id
6836      mo_utils.Get_Ledger_Info (
6837                   p_operating_unit => p_util_org_id
6838                  ,p_ledger_id      => l_order_ledger
6839                  ,p_ledger_name    => l_ord_ledger_name);
6840 
6841      ozf_utility_pvt.calculate_functional_currency (
6842                   p_from_amount => p_plan_curr_amount
6843                  ,p_conv_date     => p_exchange_rate_date
6844                  ,p_tc_currency_code => p_plan_currency_code
6845                  ,p_ledger_id => l_order_ledger
6846                  ,x_to_amount => l_conv_acctd_amount
6847                  ,x_mrc_sob_type_code => l_sob_type_code
6848                  ,x_fc_currency_code => l_fc_code
6849                  ,x_exchange_rate_type => l_exchange_rate_type
6850                  ,x_exchange_rate => l_exchange_rate
6851                  ,x_return_status => l_return_status
6852                );
6853      IF NVL(p_plan_curr_amount_rem,0) <> 0 THEN
6854         l_conv_acctd_amount_remg := l_conv_acctd_amount;
6855      END IF;
6856 
6857      --universal
6858      IF g_universal_currency = p_currency_code THEN
6859         l_conv_univ_amount := l_conv_amount;
6860      ELSIF g_universal_currency = p_plan_currency_code THEN
6861         l_conv_univ_amount := p_plan_curr_amount;
6862      ELSIF g_universal_currency = l_fc_code THEN
6863         l_conv_univ_amount := l_conv_acctd_amount;
6864      ELSE
6865      ozf_utility_pvt.convert_currency(
6866               x_return_status => l_return_status
6867              ,p_from_currency => p_plan_currency_code
6868              ,p_to_currency => g_universal_currency
6869              ,p_conv_type   => l_exchange_rate_type
6870              ,p_conv_date     => p_exchange_rate_date
6871              ,p_from_amount => p_plan_curr_amount
6872              ,x_to_amount => l_conv_univ_amount
6873              ,x_rate => l_rate
6874              );
6875      END IF;
6876 
6877      IF NVL(p_plan_curr_amount_rem,0) <> 0 THEN
6878         l_conv_univ_amount_remg := l_conv_univ_amount;
6879      END IF;
6880 
6881      --offer if null currency offer
6882      IF p_plan_currency_code = p_fund_req_currency_code THEN
6883         l_conv_fund_req_amount := p_plan_curr_amount;
6884      ELSE
6885      ozf_utility_pvt.convert_currency (
6886               x_return_status => x_return_status
6887              ,p_from_currency => p_plan_currency_code
6888              ,p_to_currency   => p_fund_req_currency_code
6889              ,p_conv_type     => l_exchange_rate_type
6890              ,p_conv_date     => p_exchange_rate_date
6891              ,p_from_amount   => p_plan_curr_amount
6892              ,x_to_amount     => l_conv_fund_req_amount
6893              ,x_rate          => l_rate
6894              );
6895      END IF;
6896 
6897      IF NVL(p_plan_curr_amount_rem,0) <> 0 THEN
6898         l_conv_fund_req_amount_remg := l_conv_fund_req_amount;
6899      END IF;
6900 
6901      --update util table
6902      UPDATE ozf_funds_utilized_all_b
6903      SET amount = l_conv_amount, amount_remaining = l_conv_amount_remg,
6904          acctd_amount = l_conv_acctd_amount, acctd_amount_remaining = l_conv_acctd_amount_remg,
6905          fund_request_amount = l_conv_fund_req_amount, fund_request_amount_remaining = l_conv_fund_req_amount_remg,
6906          univ_curr_amount = l_conv_univ_amount, univ_curr_amount_remaining = l_conv_univ_amount_remg,
6907          exchange_rate_type = l_exchange_rate_type,exchange_rate_date = p_exchange_rate_date,exchange_rate = l_exchange_rate
6908      WHERE utilization_id = p_util_utilization_id;
6909 
6910      --update summary table
6911      l_objfundsum_rec := NULL;
6912      OPEN c_get_objfundsum_rec(
6913         p_util_plan_type
6914        ,p_util_plan_id
6915        ,p_util_fund_id);
6916      FETCH c_get_objfundsum_rec INTO
6917         l_objfundsum_rec.objfundsum_id
6918         ,l_objfundsum_rec.object_version_number
6919         ,l_objfundsum_rec.utilized_amt
6920         ,l_objfundsum_rec.earned_amt
6921         ,l_objfundsum_rec.paid_amt
6922         ,l_objfundsum_rec.plan_curr_utilized_amt
6923         ,l_objfundsum_rec.plan_curr_earned_amt
6924         ,l_objfundsum_rec.plan_curr_paid_amt
6925         ,l_objfundsum_rec.univ_curr_utilized_amt
6926         ,l_objfundsum_rec.univ_curr_earned_amt
6927         ,l_objfundsum_rec.univ_curr_paid_amt;
6928      CLOSE c_get_objfundsum_rec;
6929 
6930 
6931      IF p_util_utilization_type = 'UTILIZED' OR p_adjust_paid_flag THEN
6932         l_paid_amt := p_amount;
6933         l_paid_conv_amt := l_conv_amount;
6934         l_rollup_paid_amt := p_univ_curr_amount;
6935         l_rollup_paid_conv_amt := l_conv_univ_amount;
6936         l_objfundsum_rec.paid_amt :=  NVL(l_objfundsum_rec.paid_amt, 0)
6937                                     - NVL(p_amount, 0)
6938                                     + NVL(l_conv_amount, 0);
6939         --fix for bug 8586014
6940         l_objfundsum_rec.plan_curr_paid_amt :=    NVL(l_objfundsum_rec.plan_curr_paid_amt, 0)
6941                                                 - NVL(p_fund_req_amount, 0)
6942                                                 + NVL(l_conv_fund_req_amount, 0);
6943         l_objfundsum_rec.univ_curr_paid_amt :=   NVL(l_objfundsum_rec.univ_curr_paid_amt, 0)
6944                                                - NVL(p_univ_curr_amount, 0)
6945                                                + NVL(l_conv_univ_amount, 0);
6946      END IF;
6947 
6948      l_objfundsum_rec.earned_amt := NVL(l_objfundsum_rec.earned_amt, 0)
6949                                     - NVL(p_amount, 0)
6950                                     + NVL(l_conv_amount, 0);
6951      l_objfundsum_rec.utilized_amt := NVL(l_objfundsum_rec.utilized_amt, 0)
6952                                     - NVL(p_amount, 0)
6953                                     + NVL(l_conv_amount, 0);
6954 
6955 
6956      l_objfundsum_rec.plan_curr_utilized_amt := NVL(l_objfundsum_rec.plan_curr_utilized_amt, 0)
6957                                     - NVL(p_fund_req_amount, 0)
6958                                     + NVL(l_conv_fund_req_amount, 0);
6959      --fix for bug 8586014
6960      l_objfundsum_rec.plan_curr_earned_amt := NVL(l_objfundsum_rec.plan_curr_earned_amt, 0)
6961                                     - NVL(p_fund_req_amount, 0)
6962                                     + NVL(l_conv_fund_req_amount, 0);
6963 
6964      l_objfundsum_rec.univ_curr_utilized_amt := NVL(l_objfundsum_rec.univ_curr_utilized_amt, 0)
6965                                               - NVL(p_univ_curr_amount, 0)
6966                                               + NVL(l_conv_univ_amount, 0);
6967 
6968      l_objfundsum_rec.univ_curr_earned_amt := NVL(l_objfundsum_rec.univ_curr_earned_amt, 0)
6969                                               - NVL(p_univ_curr_amount, 0)
6970                                               + NVL(l_conv_univ_amount, 0);
6971 
6972      ozf_objfundsum_pvt.update_objfundsum(p_api_version       => 1.0,
6973                                 p_init_msg_list     => Fnd_Api.G_FALSE,
6974                                 p_validation_level  => Fnd_Api.G_VALID_LEVEL_NONE,
6975                                 p_objfundsum_rec    => l_objfundsum_rec,
6976                                 x_return_status     => l_return_status,
6977                                 x_msg_count         => x_msg_count,
6978                                 x_msg_data          => x_msg_data
6979      );
6980      IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
6981         RAISE fnd_api.g_exc_unexpected_error;
6982      ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
6983         RAISE fnd_api.g_exc_error;
6984      END IF;
6985 
6986      --update activity table
6987      OPEN c_act_budget_rec(p_util_plan_id);
6988      FETCH c_act_budget_rec INTO l_act_budget_id, l_act_budget_objver;
6989      CLOSE c_act_budget_rec;
6990 
6991      UPDATE ozf_act_budgets
6992      SET  src_curr_request_amt = NVL(src_curr_request_amt, 0) - p_amount + l_conv_amount
6993           , approved_original_amount = NVL(approved_original_amount, 0) - NVL(p_fund_req_amount, 0)
6994                                                                         + NVL(l_conv_fund_req_amount,0)
6995           , approved_amount_fc = NVL(approved_amount_fc, 0) - NVL(p_acctd_amount,0)
6996                                                             + NVL(l_conv_acctd_amount,0)
6997           , request_amount     = NVL(request_amount, 0) - NVL(p_fund_req_amount, 0)
6998                                                         + NVL(l_conv_fund_req_amount, 0)
6999           , approved_amount     = NVL(approved_amount, 0) - NVL(p_fund_req_amount, 0)
7000                                                           + NVL(l_conv_fund_req_amount, 0)
7001           , last_update_date = sysdate
7002           , last_updated_by = NVL (fnd_global.user_id, -1)
7003           , last_update_login = NVL (fnd_global.conc_login_id, -1)
7004           , object_version_number = l_act_budget_objver + 1
7005      WHERE  activity_budget_id = l_act_budget_id
7006      AND    object_version_number = l_act_budget_objver;
7007 
7008      --update fund table.
7009      OPEN c_get_fund(p_util_fund_id);
7010      FETCH c_get_fund INTO l_obj_num, l_parent_fund_id, l_liability_flag,l_accrual_basis;
7011      CLOSE c_get_fund;
7012 
7013 
7014      IF p_util_utilization_type IN ('ACCRUAL', 'LEAD_ACCRUAL') THEN
7015         IF l_accrual_basis = 'CUSTOMER' AND NVL(l_liability_flag,'N')= 'N' THEN
7016            l_gl_posted_flag := G_GL_FLAG_NOLIAB;
7017         END IF;
7018      ELSIF p_util_utilization_type = 'SALES_ACCRUAL' THEN
7019         l_gl_posted_flag := G_GL_FLAG_NOLIAB;
7020      END IF;
7021 
7022      IF l_gl_posted_flag = G_GL_FLAG_NOLIAB THEN
7023         --Fix for Bug 13529250 correct values of l_orig_amt and l_rollup_orig_amt for Sales Accrual Budget
7024         l_orig_amt := NVL(l_conv_amount,0) - NVL(p_amount,0);
7025         l_rollup_orig_amt := NVL(l_conv_univ_amount,0) - NVL(p_univ_curr_amount, 0);
7026      END IF;
7027 
7028      UPDATE ozf_funds_all_b
7029      SET   original_budget = NVL(original_budget, 0) + l_orig_amt
7030           ,rollup_original_budget = NVL(rollup_original_budget, 0) + l_rollup_orig_amt
7031           ,earned_amt = NVL(earned_amt, 0) + NVL(l_conv_amount, 0)- NVL(p_amount, 0)
7032           ,paid_amt = NVL(paid_amt, 0 ) + NVL(l_paid_conv_amt, 0) - NVL(l_paid_amt, 0)
7033           ,rollup_earned_amt = NVL(rollup_earned_amt, 0) + l_rollup_orig_amt
7034           ,rollup_paid_amt   = NVL(rollup_paid_amt, 0)   + NVL(l_rollup_paid_amt, 0)
7035                                                          - NVL(l_rollup_paid_conv_amt, 0)
7036           ,object_version_number = l_obj_num + 1
7037      WHERE fund_id =  p_util_fund_id
7038      AND   object_version_number = l_obj_num;
7039 
7040      IF l_parent_fund_id is NOT NULL THEN
7041      FOR fund IN c_parent(l_parent_fund_id)
7042      LOOP
7043         UPDATE ozf_funds_all_b
7044         SET object_version_number = fund.object_version_number + 1
7045           ,rollup_earned_amt = NVL(rollup_earned_amt,0) + l_rollup_orig_amt
7046 
7047           ,rollup_paid_amt = NVL(rollup_paid_amt,0) + NVL(l_rollup_paid_amt,0)
7048                                                     - NVL(l_rollup_paid_conv_amt, 0)
7049           ,rollup_original_budget = NVL(rollup_original_budget,0) + l_rollup_orig_amt
7050 
7051         WHERE fund_id = fund.fund_id
7052         AND object_version_number = fund.object_version_number;
7053      END LOOP;
7054      END IF;
7055 
7056 
7057 
7058    EXCEPTION
7059      WHEN OTHERS THEN
7060        ROLLBACK TO recalculate_earnings_sp;
7061        ozf_utility_pvt.write_conc_log('recalculate_earnings(): exception ');
7062        fnd_msg_pub.count_and_get (
7063             p_count    => l_msg_count,
7064             p_data     => l_msg_data,
7065             p_encoded  => fnd_api.g_false
7066        );
7067 
7068 
7069      x_return_status := fnd_api.g_ret_sts_success;
7070      IF g_debug_flag = 'Y' THEN
7071         ozf_utility_pvt.write_conc_log ('    D: recalculate_earnings() ENDs for utilization id ' || p_util_utilization_id);
7072      END IF;
7073    END recalculate_earnings;
7074 END ozf_accrual_engine;