DBA Data[Home] [Help]

PACKAGE BODY: APPS.OZF_ACCRUAL_ENGINE

Source


1 PACKAGE BODY OZF_ACCRUAL_ENGINE AS
2 /* $Header: ozfacreb.pls 120.56.12010000.5 2009/02/18 07:08:48 psomyaju 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 -------------------------------------------------------------------------------
97    g_pkg_name   CONSTANT VARCHAR2 (30) := 'OZF_ACCRUAL_ENGINE';
98    g_recal_flag CONSTANT VARCHAR2(1) :=  NVL(fnd_profile.value('OZF_BUDGET_ADJ_ALLOW_RECAL'),'N');
99    g_debug_flag      VARCHAR2 (1) := 'N';
100    G_DEBUG      BOOLEAN := FND_MSG_PUB.check_msg_level(FND_MSG_PUB.g_msg_lvl_debug_high);
101    g_universal_currency   CONSTANT VARCHAR2 (15) := fnd_profile.VALUE ('OZF_UNIV_CURR_CODE');
102    g_order_gl_phase   CONSTANT VARCHAR2 (15) := NVL(fnd_profile.VALUE ('OZF_ORDER_GLPOST_PHASE'), 'SHIPPED');
103    g_bulk_limit  CONSTANT NUMBER := 5000;  -- yzhao: Sep 8,2005 bulk fetch limit. It should get from profile.
104 
105    TYPE utilIdTbl       IS TABLE OF ozf_funds_utilized_all_b.utilization_id%TYPE;
106    TYPE objVerTbl       IS TABLE OF ozf_funds_utilized_all_b.object_version_number%TYPE;
107    TYPE amountTbl       IS TABLE OF ozf_funds_utilized_all_b.amount%TYPE;
108    TYPE planTypeTbl     IS TABLE OF ozf_funds_utilized_all_b.plan_type%TYPE;
109    TYPE planIdTbl       IS TABLE OF ozf_funds_utilized_all_b.plan_id%TYPE;
110    TYPE planAmtTbl      IS TABLE OF ozf_funds_utilized_all_b.plan_curr_amount%TYPE;
111    TYPE utilTypeTbl     IS TABLE OF ozf_funds_utilized_all_b.utilization_type%TYPE;
112    TYPE fundIdTbl       IS TABLE OF ozf_funds_utilized_all_b.fund_id%TYPE;
113    TYPE acctAmtTbl      IS TABLE OF ozf_funds_utilized_all_b.acctd_amount%TYPE;
114    TYPE glDateTbl       IS TABLE OF ozf_funds_utilized_all_b.gl_date%TYPE;
115    TYPE orgIdTbl        IS TABLE OF ozf_funds_utilized_all_b.org_id%TYPE;
116    TYPE priceAdjTbl     IS TABLE OF ozf_funds_utilized_all_b.price_adjustment_id%TYPE         ;
117    TYPE objectIdTbl     IS TABLE OF ozf_funds_utilized_all_b.object_id%TYPE         ;
118 
119 ----------------------------------------------------------------------------------
120 -- Procedure Name
121 --  calculate_accrual_amount
122 -- created by mpande 07/20/2000
123 -- 02/13/2002 updated for negative adjustment amount
124 -- Purpose
125 --   This procedure will accept p_src_id which could be a CAMP_id or a FUND_ID
126 -- and return a PL/SQL table which consists all the funds rolled up to the first level
127 -- with  its contribution amount
128 -----------------------------------------------------------------------------------
129 
130 PROCEDURE calculate_accrual_amount (
131       x_return_status   OUT NOCOPY      VARCHAR2,
132       p_src_id          IN       NUMBER,
133       p_earned_amt      IN       NUMBER,
134       p_cust_account_type IN     VARCHAR2 := NULL,
135       p_cust_account_id IN       NUMBER  := NULL,
136       p_product_item_id IN       NUMBER  := NULL,
137       x_fund_amt_tbl    OUT NOCOPY      ozf_fund_amt_tbl_type
138    ) IS
139 
140 -- rimehrot, for R12: query from the new table
141 
142      CURSOR c_budget (p_src_id IN NUMBER) IS
143         SELECT fund_id parent_source_id, committed_amt total_amount , fund_currency parent_curr
144         FROM ozf_object_fund_summary
145         WHERE object_type = 'OFFR'
146         AND object_id = p_src_id
147         --AND NVL(committed_amt, 0) <> 0
148         ORDER BY fund_id;
149 
150       --- local variables
151       l_count           NUMBER            := 0;
152       l_return_status   VARCHAR2 (30);
153       l_msg_count                  NUMBER;
154       l_msg_data                   VARCHAR2 (2000);
155       l_rate            NUMBER;
156       l_total_amount    NUMBER            := 0;
157       l_budget_offer_yn  VARCHAR2(1);
158       l_utilized_amount    NUMBER;
159       l_eligible_fund_amt_tbl        ozf_fund_amt_tbl_type;
160       l_eligible_count  NUMBER            := 0;
161       l_eligible_total_amount      NUMBER  := 0;
162       l_eligible_flag              BOOLEAN := false;
163       l_converted_amt       NUMBER;
164 
165       TYPE parentIdType     IS TABLE OF ozf_object_fund_summary.fund_id%TYPE;
166       TYPE amountType       IS TABLE OF ozf_object_fund_summary.committed_amt%TYPE;
167       TYPE currencyType     IS TABLE OF ozf_object_fund_summary.fund_currency%TYPE;
168       TYPE fraction_tbl_type IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
169       l_parent_id_tbl       parentIdType;
170       l_total_amount_tbl    amountType;
171       l_parent_curr_tbl     currencyType;
172       l_fraction_tbl    fraction_tbl_type;
173 
174       -- cursor for accrual budget
175       CURSOR c_offer_info  IS
176          SELECT NVL(budget_offer_yn,'N')
177          FROM ozf_offers
178          WHERE qp_list_header_id = p_src_id;
179       -- cursor for accrual fund
180       CURSOR c_fund  IS
181          SELECT fund_id , currency_code_tc
182          FROM ozf_funds_all_b
183          WHERE plan_id = p_src_id;
184 
185       /* yzhao: 10/03/2003 fix bug 3156515 - PROMOTIONAL GOODS OFFER EXCEEDS THE BUDGET AMOUNT
186                    get utilized amount.
187            -- rimehrot, commented for R12: use ozf_object_fund_summary table directly.
188            CURSOR c_get_utilized_amount(p_offer_id IN NUMBER, p_fund_id IN NUMBER) IS
189            SELECT   SUM(NVL(a2.amount, 0)) amount
190            FROM   ozf_funds_utilized_all_b a2
191            WHERE  a2.plan_id = p_offer_id
192            AND  a2.plan_type = 'OFFR'
193            AND  a2.fund_id = p_fund_id
194            AND  a2.utilization_type NOT IN ('REQUEST', 'TRANSFER', 'SALES_ACCRUAL');
195         */
196           -- rimehrot, for R12: use ozf_object_fund_summary directly to get utilized amount.
197       CURSOR c_get_utilized_amount(p_offer_id IN NUMBER, p_fund_id IN NUMBER) IS
198          SELECT utilized_amt
199          FROM ozf_object_fund_summary
200          WHERE fund_id = p_fund_id
201          AND object_type = 'OFFR'
202          AND object_id = p_offer_id;
203 
204    BEGIN
205       x_return_status            := fnd_api.g_ret_sts_success;
206 
207       IF g_debug_flag = 'Y' THEN
208          ozf_utility_pvt.write_conc_log('    D: ENTER calculate_accrual_amount   offer_id=' || p_src_id || '  p_earned_amt=' || p_earned_amt);
209       END IF;
210 
211       /*  kdass 31-JAN-05 - fix 11.5.9 bug 4067266 - RETROACTIVE VOLUME BUDGETS DO NOT CALCULATE CORRECTLY WHEN THE 1ST TIER IS AT 0%
212       IF p_earned_amt = 0 THEN
213          RETURN;
214       END IF;
215       */
216       -- check if it is a accrual budget
217       OPEN c_offer_info;
218       FETCH c_offer_info INTO l_budget_offer_yn ;
219       CLOSE c_offer_info;
220       -- For positive accruals for a fully accrued budget we have only one budget for that
221       /* yzhao: 04/04/2003 for fully accrued budget, only one budget. No matter it's positive or negative(return)
222       IF p_earned_amt > 0 AND l_budget_offer_yn = 'Y' THEN
223        */
224       IF l_budget_offer_yn = 'Y' THEN
225          l_count := 1;
226          OPEN c_fund;
227          FETCH c_fund INTO      x_fund_amt_tbl (l_count).ofr_src_id,
228                                 x_fund_amt_tbl (l_count).budget_currency;
229          CLOSE c_fund;
230          x_fund_amt_tbl (l_count).earned_amount := p_earned_amt;
231          RETURN ;
232       END IF ;
233 
234       -- first get the total committed amount
235       OPEN c_budget (p_src_id);
236       LOOP
237         FETCH c_budget BULK COLLECT INTO l_parent_id_tbl, l_total_amount_tbl, l_parent_curr_tbl LIMIT g_bulk_limit;
238 
239         FOR i IN NVL(l_parent_id_tbl.FIRST, 1) .. NVL(l_parent_id_tbl.LAST, 0) LOOP
240             -- if recalculate is allowed, always calculate based on committed amount
241             -- otherwise, calculate based on available amount
242             IF g_recal_flag = 'Y' THEN
243                 l_count := l_count + 1;
244                 x_fund_amt_tbl (l_count).ofr_src_id := l_parent_id_tbl(i);
245                 x_fund_amt_tbl (l_count).earned_amount := l_total_amount_tbl(i);
246                 x_fund_amt_tbl (l_count).budget_currency:= l_parent_curr_tbl(i);
247             ELSE
248                 -- recalculate is not allowed, always calculate based on available amount
249                /* yzhao: 10/03/2003 fix bug 3156515 - PROMOTIONAL GOODS OFFER EXCEEDS THE BUDGET AMOUNT
250                            fraction calculation: this budget's committed amount for this offer / all budget's total committed amount for this offer
251                            for positive accrual posting,
252                                if recalculate committed flag is ON, posting amount = p_earned_amount * fraction
253                                else, posting amount = LEAST(p_earned_amount * fraction, this budget's committed amount - utilized amount)
254                            for negative accrual posting,
255                                posting amount = -LEAST(abs(p_earned_amount) * fraction, this budget's committed amount - utilized amount)
256                */
257                OPEN c_get_utilized_amount( p_offer_id => p_src_id
258                                          , p_fund_id => l_parent_id_tbl(i));
259                FETCH c_get_utilized_amount INTO l_utilized_amount;
260                CLOSE c_get_utilized_amount;
261 
262                IF l_total_amount_tbl(i) <= l_utilized_amount THEN   -- !!! think about negative utilized amount!
263                   -- no available amount. next iteration
264                   GOTO LABEL_FOR_NEXT_ITERATION;
265                END IF;
266 
267                l_count := l_count + 1;
268                x_fund_amt_tbl (l_count).ofr_src_id := l_parent_id_tbl(i);
269                x_fund_amt_tbl (l_count).earned_amount := l_total_amount_tbl(i) - NVL(l_utilized_amount, 0);
270                x_fund_amt_tbl (l_count).budget_currency:= l_parent_curr_tbl(i);
271             END IF;  -- IF g_recal_flag = 'Y'
272             IF g_debug_flag = 'Y' THEN
273                ozf_utility_pvt.write_conc_log('    D: calculate_accrual_amount: ' || l_count || ') fund_id=' || x_fund_amt_tbl (l_count).ofr_src_id
274                   || ' utilized_amount=' || l_utilized_amount || x_fund_amt_tbl (l_count).budget_currency);
275             END IF;
276             -- if the currencies of the budgets are different then convert it into the first budget currency
277             -- to get the total amount
278             IF l_count  > 1 THEN
279                IF x_fund_amt_tbl (l_count).budget_currency <>
280                                                        x_fund_amt_tbl (l_count - 1).budget_currency THEN
281                   ozf_utility_pvt.convert_currency (
282                      x_return_status=> x_return_status,
283                      p_from_currency=> x_fund_amt_tbl (l_count).budget_currency,
284                      p_to_currency=> x_fund_amt_tbl (l_count - 1).budget_currency,
285                      p_from_amount=> x_fund_amt_tbl (l_count).earned_amount,
286                      x_to_amount=> l_converted_amt,
287                      x_rate=> l_rate
288                   );
289                   x_fund_amt_tbl (l_count).earned_amount := l_converted_amt;
290 
291                END IF;
292                l_total_amount := l_total_amount + x_fund_amt_tbl (l_count).earned_amount;
293             ELSE
294                l_total_amount := x_fund_amt_tbl (l_count).earned_amount;
295             END IF;
296 
297             If l_parent_id_tbl.COUNT > 1 THEN
298                ozf_budgetapproval_pvt.check_budget_qualification(
299                   p_budget_id          => x_fund_amt_tbl (l_count).ofr_src_id
300                 , p_cust_account_id    => p_cust_account_id
301                 , p_product_item_id    => p_product_item_id
302                 , x_qualify_flag       => l_eligible_flag
303                 , x_return_status      => l_return_status
304                 , x_msg_count          => l_msg_count
305                 , x_msg_data           => l_msg_data
306                );
307 
308                IF g_debug_flag = 'Y' THEN
309                   ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): check_budget_qualification status:   ' || l_return_status);
310                END IF;
311                IF l_return_status <> fnd_api.g_ret_sts_success THEN
312                   l_eligible_flag := false;
313                END IF;
314             ELSE
315                l_eligible_flag := true;
316             END IF;
317 
318             IF l_eligible_flag THEN
319                IF g_debug_flag = 'Y' THEN
320                   ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): budget ' || x_fund_amt_tbl (l_count).ofr_src_id
321                      || ' is qualified for product:' || p_product_item_id || ' customer: ' || p_cust_account_id);
322                END IF;
323                l_eligible_count := l_eligible_count + 1;
324                l_eligible_fund_amt_tbl (l_eligible_count).ofr_src_id := x_fund_amt_tbl (l_count).ofr_src_id;
325                l_eligible_fund_amt_tbl (l_eligible_count).earned_amount := x_fund_amt_tbl (l_count).earned_amount;
326                l_eligible_fund_amt_tbl (l_eligible_count).budget_currency:= x_fund_amt_tbl (l_count).budget_currency;
327                l_eligible_total_amount := l_eligible_total_amount + l_eligible_fund_amt_tbl (l_eligible_count).earned_amount;
328             ELSE
329                IF g_debug_flag = 'Y' THEN
330                   ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): budget ' || x_fund_amt_tbl (l_count).ofr_src_id
331                      || ' is not qualified for product:' || p_product_item_id || ' customer: ' || p_cust_account_id);
332                END IF;
333             END IF;
334 
335             <<LABEL_FOR_NEXT_ITERATION>>
336             NULL;
337         END LOOP;  -- FOR i IN NVL(l_parent_id_tbl.FIRST, 1) .. NVL(l_parent_id_tbl.LAST, 0) LOOP
338         EXIT WHEN c_budget%NOTFOUND;
339       END LOOP;  -- c_budget
340       CLOSE c_budget;
341 
342       IF l_eligible_total_amount > 0 THEN
343           x_fund_amt_tbl.DELETE;
344           x_fund_amt_tbl := l_eligible_fund_amt_tbl;
345           l_total_amount := l_eligible_total_amount;
346           l_count := l_eligible_count;
347           IF g_debug_flag = 'Y' THEN
348              ozf_utility_pvt.write_conc_log('    D: calculate_accrual_amount(): ' || l_count
349                 || ' eligible budgets found. Total amount available for posting:' || l_total_amount);
350           END IF;
351       END IF;
352 
353       -- Note that the amounts are in one currency
354       IF l_total_amount = 0 THEN
355          IF g_recal_flag = 'N' and p_earned_amt < 0 THEN    -- ??? really needed ???
356             x_return_status            := fnd_api.g_ret_sts_error;
357             RETURN;
358          END IF;
359       END IF;
360 
361       IF g_debug_flag = 'Y' THEN
362          ozf_utility_pvt.write_conc_log('    D: calculate_accrual_amount(): g_recal_flag=' || g_recal_flag || ' p_earned_amt=' || p_earned_amt
363             || ' final sourcing budget table count=' || x_fund_amt_tbl.COUNT || ' sourcing budgets total amount=' || l_total_amount);
364       END IF;
365 
366       -- calculate the fraction if recalculation flag is on, or to_post amount is less than available amount
367       -- otherwise, use whatever available amount
368       IF g_recal_flag = 'Y' OR p_earned_amt < l_total_amount THEN
369           FOR i IN NVL (x_fund_amt_tbl.FIRST, 1) .. NVL (x_fund_amt_tbl.LAST, 0)
370           LOOP
371              IF l_total_amount = 0 THEN
372                  l_fraction_tbl (x_fund_amt_tbl (i).ofr_src_id) := 1;
373              ELSE
374                  l_fraction_tbl (x_fund_amt_tbl (i).ofr_src_id) :=
375                                                       x_fund_amt_tbl (i).earned_amount / l_total_amount;
376              END IF;
377           END LOOP;
378 
379           FOR i IN NVL (x_fund_amt_tbl.FIRST, 1) .. NVL (x_fund_amt_tbl.LAST, 0)
380           LOOP
381               x_fund_amt_tbl (i).earned_amount :=
382                            p_earned_amt * l_fraction_tbl (x_fund_amt_tbl (i).ofr_src_id);
383               IF g_debug_flag = 'Y' THEN
384                  ozf_utility_pvt.write_conc_log ('    D: calculate_accrual_amount(): --index--'  || i  || '--final posting amt--'
385                                 || x_fund_amt_tbl (i).earned_amount
386                                 || '--fund id--' || x_fund_amt_tbl (i).ofr_src_id
387                                 || '--fraction--' || l_fraction_tbl(x_fund_amt_tbl (i).ofr_src_id));
388               END IF;
389           END LOOP;
390       END IF;
391 
392    EXCEPTION
393       WHEN OTHERS THEN
394          IF c_budget%ISOPEN THEN
395             CLOSE c_budget;
396          END IF;
397          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
398             fnd_msg_pub.add_exc_msg (g_pkg_name, 'Calculate Accrual');
399          END IF;
400          x_return_status            := fnd_api.g_ret_sts_unexp_error;
401    END calculate_accrual_amount;
402 
403   /*****************************************************************************************/
404 -- Start of Comments
405 --
406 -- NAME
407 --   Create_Act_Budgets
408 --
409 -- PURPOSE
410 --   This procedure is to create a act_budget record
411 --
412 -- HISTORY
413 -- 01/22/2003  feliu  CREATED
414 
415 -- End of Comments
416 /*****************************************************************************************/
417    PROCEDURE create_actbudgets_rec (
418       x_return_status      OUT NOCOPY      VARCHAR2
419      ,x_msg_count          OUT NOCOPY      NUMBER
420      ,x_msg_data           OUT NOCOPY      VARCHAR2
421      ,x_act_budget_id      OUT NOCOPY      NUMBER
422      ,p_act_budgets_rec    IN              ozf_actbudgets_pvt.act_budgets_rec_type
423      ,p_ledger_id          IN              NUMBER
424      ,p_org_id             IN              NUMBER DEFAULT NULL -- added for bug 7030415
425     ) IS
426       l_api_name      CONSTANT VARCHAR2 (30)        := 'create_actbudgets_rec';
427       l_full_name     CONSTANT VARCHAR2 (60)        :=    g_pkg_name
428                                                        || '.'
429                                                        || l_api_name;
430       l_return_status         VARCHAR2 (1); -- Return value from procedures
431       l_act_budgets_rec       ozf_actbudgets_pvt.act_budgets_rec_type := p_act_budgets_rec;
432       l_requester_id          NUMBER;
433       l_activity_id           NUMBER;
434       l_obj_ver_num           NUMBER;
435       l_old_approved_amount   NUMBER;
436       l_set_of_book_id        NUMBER;
437       l_sob_type_code         VARCHAR2(30);
438       l_fc_code               VARCHAR2(150);
439       l_exchange_rate_type    VARCHAR2(150);
440       l_exchange_rate         NUMBER;
441       l_approved_amount_fc    NUMBER;
442       l_old_amount_fc         NUMBER;
443 
444       CURSOR c_act_budget_id IS
445          SELECT ozf_act_budgets_s.NEXTVAL
446          FROM DUAL;
447 
448       CURSOR c_act_util_rec (p_used_by_id IN NUMBER, p_used_by_type IN VARCHAR2) IS
449          SELECT activity_budget_id, object_version_number, approved_amount,approved_amount_fc
450          FROM ozf_act_budgets
451          WHERE act_budget_used_by_id = p_used_by_id
452          AND arc_act_budget_used_by = p_used_by_type
453          AND transfer_type = 'UTILIZED';
454 
455       -- added for bug 7030415
456       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
457          SELECT exchange_rate_type
458          FROM   ozf_sys_parameters_all
459          WHERE  org_id = p_org_id;
460 
461    BEGIN
462       IF g_debug_flag = 'Y' THEN
463          ozf_utility_pvt.write_conc_log(   l_full_name
464                                      || ': start');
465       END IF;
466       -- Standard Start of API savepoint
467       SAVEPOINT create_actbudgets_rec;
468 
469       --  Initialize API return status to success
470       x_return_status            := fnd_api.g_ret_sts_success;
471 
472 
473       OPEN c_act_util_rec (
474          p_act_budgets_rec.act_budget_used_by_id,
475          p_act_budgets_rec.arc_act_budget_used_by
476       );
477       FETCH c_act_util_rec INTO l_activity_id,
478                                 l_obj_ver_num,
479                                 l_old_approved_amount,
480                                 l_old_amount_fc;
481       CLOSE c_act_util_rec;
482 
483       --if act_budget record exist for this offer, update record.
484       IF l_activity_id IS NOT NULL THEN
485          UPDATE ozf_act_budgets
486          SET  request_amount = l_old_approved_amount + NVL(l_act_budgets_rec.request_amount, 0),
487               approved_amount =l_old_approved_amount + NVL(l_act_budgets_rec.request_amount, 0),
488               src_curr_request_amt =l_old_approved_amount + NVL(l_act_budgets_rec.request_amount, 0),
489               object_version_number = l_obj_ver_num + 1
490               ,parent_source_id = l_act_budgets_rec.parent_source_id
491               ,parent_src_curr  = l_act_budgets_rec.parent_src_curr
492               ,parent_src_apprvd_amt =l_act_budgets_rec.parent_src_apprvd_amt
493               ,approved_amount_fc = NVL(l_old_amount_fc,0) + NVL(l_approved_amount_fc,0)
494               ,approved_original_amount = l_old_approved_amount + l_act_budgets_rec.request_amount
495          WHERE activity_budget_id = l_activity_id
496              AND object_version_number = l_obj_ver_num;
497          x_act_budget_id := l_activity_id;
498 
499          IF (SQL%NOTFOUND) THEN
500             -- Error, check the msg level and added an error message to the
501             -- API message list
502             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
503                fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
504                fnd_msg_pub.ADD;
505             END IF;
506             RAISE fnd_api.g_exc_unexpected_error;
507          END IF;
508 
509          RETURN; -- exit from program.
510       END IF;
511 
512       IF l_act_budgets_rec.request_currency IS NULL THEN
513          ozf_utility_pvt.write_conc_log ('OZF_ACT_BUDG_NO_CURRENCY');
514          x_return_status            := fnd_api.g_ret_sts_error;
515       END IF;
516 
517       /* Added for bug 7030415
518        This currency conversion is for approved_amount_fc column in ozf_act_budgets table.
519        Using the utilization org_id because to_currency is the functional currency of
520        order's org's ledger.*/
521 
522       OPEN c_get_conversion_type(p_org_id);
523       FETCH c_get_conversion_type INTO l_exchange_rate_type;
524       CLOSE c_get_conversion_type;
525 
526         IF g_debug_flag = 'Y' THEN
527           ozf_utility_pvt.write_conc_log('**************************START****************************');
528           ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_act_budgets_rec.request_amount );
529           ozf_utility_pvt.write_conc_log(l_api_name||' From Curr: '||l_act_budgets_rec.request_currency );
530           ozf_utility_pvt.write_conc_log(l_api_name||' p_ledger_id: '||p_ledger_id);
531           ozf_utility_pvt.write_conc_log(l_api_name||' l_exchange_rate_type: '|| l_exchange_rate_type);
532           ozf_utility_pvt.write_conc_log('Request amount is converted from request curr to functional curr');
533         END IF;
534 
535       IF l_act_budgets_rec.request_amount <> 0 THEN
536          ozf_utility_pvt.calculate_functional_currency (
537                p_from_amount=>l_act_budgets_rec.request_amount
538               ,p_tc_currency_code=> l_act_budgets_rec.request_currency
539               ,p_ledger_id => p_ledger_id
540               ,x_to_amount=> l_approved_amount_fc
541               ,x_mrc_sob_type_code=> l_sob_type_code
542               ,x_fc_currency_code=> l_fc_code
543               ,x_exchange_rate_type=> l_exchange_rate_type
544               ,x_exchange_rate=> l_exchange_rate
545               ,x_return_status=> l_return_status
546             );
547          IF g_debug_flag = 'Y' THEN
548             ozf_utility_pvt.write_conc_log(l_full_name || 'calculate_functional_curr: ' || l_return_status);
549          END IF;
550 
551          IF l_return_status = fnd_api.g_ret_sts_error THEN
552             RAISE fnd_api.g_exc_error;
553          ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
554             RAISE fnd_api.g_exc_unexpected_error;
555          END IF;
556       END IF;
557 
558       OPEN c_act_budget_id;
559       FETCH c_act_budget_id INTO l_act_budgets_rec.activity_budget_id;
560       CLOSE c_act_budget_id;
561 
562       l_requester_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
563 
564       INSERT INTO ozf_act_budgets
565                   (activity_budget_id,last_update_date
566                   ,last_updated_by, creation_date
567                   ,created_by,last_update_login -- other columns
568                   ,object_version_number,act_budget_used_by_id
569                   ,arc_act_budget_used_by,budget_source_type
570                   ,budget_source_id,transaction_type
571                   ,request_amount,request_currency
572                   ,request_date,user_status_id
573                   ,status_code,approved_amount
574                   ,approved_original_amount,approved_in_currency
575                   ,approval_date, approver_id
576                   ,spent_amount, partner_po_number
577                   ,partner_po_date, partner_po_approver
578                   ,posted_flag, adjusted_flag
579                   ,parent_act_budget_id, contact_id
580                   ,reason_code, transfer_type
581                   ,requester_id,date_required_by
582                   ,parent_source_id,parent_src_curr
583                   ,parent_src_apprvd_amt,partner_holding_type
584                   ,partner_address_id, vendor_id
585                   ,owner_id,recal_flag
586                   ,attribute_category, attribute1
587                   ,attribute2, attribute3
588                   ,attribute4, attribute5
589                   ,attribute6, attribute7
590                   ,attribute8, attribute9
591                   ,attribute10, attribute11
592                   ,attribute12, attribute13
593                   ,attribute14, attribute15
594                   ,approved_amount_fc
595                   ,src_curr_request_amt
596                   )
597            VALUES (l_act_budgets_rec.activity_budget_id,SYSDATE
598                    ,fnd_global.user_id, SYSDATE
599                    ,fnd_global.user_id, fnd_global.conc_login_id
600                    ,1, l_act_budgets_rec.act_budget_used_by_id
601                    ,l_act_budgets_rec.arc_act_budget_used_by, l_act_budgets_rec.budget_source_type
602                   ,l_act_budgets_rec.budget_source_id, l_act_budgets_rec.transaction_type
603                   ,l_act_budgets_rec.request_amount, l_act_budgets_rec.request_currency
604                   ,SYSDATE, l_act_budgets_rec.user_status_id
605                   ,NVL(l_act_budgets_rec.status_code, 'NEW'), l_act_budgets_rec.approved_amount
606                   ,l_act_budgets_rec.approved_amount,l_act_budgets_rec.approved_in_currency
607                   ,sysdate,l_requester_id
608                   ,l_act_budgets_rec.spent_amount, l_act_budgets_rec.partner_po_number
609                   ,l_act_budgets_rec.partner_po_date, l_act_budgets_rec.partner_po_approver
610                   ,l_act_budgets_rec.posted_flag, l_act_budgets_rec.adjusted_flag
611                   ,l_act_budgets_rec.parent_act_budget_id, l_act_budgets_rec.contact_id
612                   ,l_act_budgets_rec.reason_code, l_act_budgets_rec.transfer_type
613                   ,l_requester_id,l_act_budgets_rec.date_required_by
614                   ,l_act_budgets_rec.parent_source_id,l_act_budgets_rec.parent_src_curr
615                   ,l_act_budgets_rec.parent_src_apprvd_amt,l_act_budgets_rec.partner_holding_type
616                   ,l_act_budgets_rec.partner_address_id, l_act_budgets_rec.vendor_id
617                   ,NULL,l_act_budgets_rec.recal_flag
618                   ,l_act_budgets_rec.attribute_category, l_act_budgets_rec.attribute1
619                   ,l_act_budgets_rec.attribute2, l_act_budgets_rec.attribute3
620                   ,l_act_budgets_rec.attribute4, l_act_budgets_rec.attribute5
621                   ,l_act_budgets_rec.attribute6, l_act_budgets_rec.attribute7
622                   ,l_act_budgets_rec.attribute8, l_act_budgets_rec.attribute9
623                   ,l_act_budgets_rec.attribute10, l_act_budgets_rec.attribute11
624                   ,l_act_budgets_rec.attribute12, l_act_budgets_rec.attribute13
625                   ,l_act_budgets_rec.attribute14, l_act_budgets_rec.attribute15
626                   ,l_approved_amount_fc
627                   ,l_act_budgets_rec.approved_amount);
628 
629       x_act_budget_id := l_act_budgets_rec.activity_budget_id;
630 
631       IF g_debug_flag = 'Y' THEN
632          ozf_utility_pvt.write_conc_log(   l_api_name
633                                      || ': insert complete' || l_act_budgets_rec.activity_budget_id);
634       END IF;
635 
636           -- Standard call to get message count AND IF count is 1, get message info.
637       fnd_msg_pub.count_and_get (
638             p_count=> x_msg_count,
639             p_data=> x_msg_data,
640             p_encoded=> fnd_api.g_false
641       );
642 
643    EXCEPTION
644       WHEN fnd_api.g_exc_error THEN
645          ROLLBACK TO create_actbudgets_rec;
646          x_return_status            := fnd_api.g_ret_sts_error;
647          fnd_msg_pub.count_and_get (
648             p_count=> x_msg_count,
649             p_data=> x_msg_data,
650             p_encoded=> fnd_api.g_false
651          );
652 
653       WHEN fnd_api.g_exc_unexpected_error THEN
654          ROLLBACK TO create_actbudgets_rec;
655          x_return_status            := fnd_api.g_ret_sts_unexp_error;
656          fnd_msg_pub.count_and_get (
657             p_count=> x_msg_count,
658             p_data=> x_msg_data,
659             p_encoded=>fnd_api.g_false
660          );
661 
662       WHEN OTHERS THEN
663          ROLLBACK TO create_actbudgets_rec;
664          x_return_status            := fnd_api.g_ret_sts_unexp_error;
665 
666          fnd_msg_pub.count_and_get (
667             p_count=> x_msg_count,
668             p_data=> x_msg_data,
669             p_encoded=> fnd_api.g_false
670          );
671 
672    END create_actbudgets_rec;
673 
674   ---------------------------------------------------------------------
675 -- PROCEDURE
676 --    Create_Utilized_Rec
677 --
678 -- HISTORY
679 --    01/22/2003  feliu  Create.
680 --    10/14/2003  yzhao  Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
681 --    11/25/2003  yzhao  11.5.10 populate utilized_amt and earned_amt
682 ---------------------------------------------------------------------
683 
684    PROCEDURE create_utilized_rec (
685      x_return_status      OUT NOCOPY      VARCHAR2
686      ,x_msg_count          OUT NOCOPY      NUMBER
687      ,x_msg_data           OUT NOCOPY      VARCHAR2
688      ,x_utilization_id      OUT NOCOPY      NUMBER
689      ,p_utilization_rec    IN       ozf_fund_utilized_pvt.utilization_rec_type
690    ) IS
691       l_api_name            CONSTANT VARCHAR2 (30)     := 'create_utilized_rec';
692       l_full_name           CONSTANT VARCHAR2 (60)     :=    g_pkg_name || '.' || l_api_name;
693       l_return_status                VARCHAR2 (1);
694       l_utilization_rec              ozf_fund_utilized_pvt.utilization_rec_type := p_utilization_rec;
695       l_earned_amt                   NUMBER;
696       l_obj_num                      NUMBER;
697       l_fund_type                    VARCHAR2 (30);
698       l_parent_fund_id               NUMBER;
699       l_accrual_basis                VARCHAR2 (30);
700       l_original_budget              NUMBER;
701       l_event_id                     NUMBER;
702       /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
703       l_mc_record_id                 NUMBER;
704       l_mc_obj_num                   NUMBER;
705       l_mc_col_1                     NUMBER;
706       l_mc_col_6                     NUMBER;
707       l_mc_col_7                     NUMBER;
708       l_mc_col_8                     NUMBER;
709       l_mc_col_9                     NUMBER;
710        */
711       l_offer_type                   VARCHAR2 (30);
712       l_accrual_flag                 VARCHAR2 (1);
713       l_set_of_book_id               NUMBER;
714       l_sob_type_code                VARCHAR2 (30);
715       l_fc_code                      VARCHAR2 (150);
716       l_fund_rec                     ozf_funds_pvt.fund_rec_type;
717       l_rollup_orig_amt           NUMBER;
718       l_rollup_earned_amt         NUMBER;
719       l_new_orig_amt              NUMBER;
720       l_new_utilized_amt          NUMBER;
721       l_new_earned_amt            NUMBER;
722       l_rate                      NUMBER;
723       l_univ_amt                  NUMBER;
724       l_new_paid_amt              NUMBER;
725       l_new_univ_amt              NUMBER;
726       l_paid_amt                  NUMBER;
727       l_rollup_paid_amt           NUMBER;
728       l_committed_amt             NUMBER;
729       l_rollup_committed_amt      NUMBER;
730       -- yzhao: 10/14/2003 added
731       l_new_committed_amt         NUMBER;
732       l_new_recal_committed       NUMBER;
733       l_recal_committed           NUMBER;
734       l_rollup_recal_committed    NUMBER;
735       l_plan_id                   NUMBER;
736       l_act_budget_id             NUMBER;
737       l_act_budget_objver         NUMBER;
738       l_liability_flag            VARCHAR2(1);
739       -- yzhao: 11.5.10
740       l_utilized_amt              NUMBER;
741       l_rollup_utilized_amt       NUMBER;
742       l_off_invoice_gl_post_flag  VARCHAR2(1);
743       l_order_ledger              NUMBER;
744       l_ord_ledger_name           VARCHAR2(150);
745       l_fund_ledger               NUMBER;
746       l_custom_setup_id           NUMBER;
747       l_beneficiary_account_id    NUMBER;
748       l_req_header_id             NUMBER;
749       -- rimehrot: added for R12
750       l_plan_currency                VARCHAR2 (150);
751       l_objfundsum_rec               ozf_objfundsum_pvt.objfundsum_rec_type := NULL;
752       l_objfundsum_id                NUMBER;
753       l_offer_id                     NUMBER;
754 
755       --nirprasa
756       l_autopay_party_attr       VARCHAR2(30);
757       l_autopay_party_id         NUMBER;
758 
759 --Added variable for bug 6278466
760       l_org_id                    NUMBER; -- removed initialization for bug 6278466
761 
762 --Added c_site_org_id for bug 6278466
763       CURSOR c_site_org_id (p_site_use_id IN NUMBER) IS
764          SELECT org_id
765            FROM hz_cust_site_uses_all
766           WHERE site_use_id = p_site_use_id;
767 
768       -- Cursor to get the sequence for utilization_id
769       CURSOR c_utilization_seq IS
770          SELECT ozf_funds_utilized_s.NEXTVAL
771          FROM DUAL;
772 
773       -- Cursor to get fund earned amount and object_version_number
774       CURSOR c_fund_b (p_fund_id IN NUMBER) IS
775          SELECT object_version_number
776                ,accrual_basis
777                ,fund_type
778                ,original_budget
779                ,earned_amt
780                ,paid_amt
781                ,parent_fund_id
782                ,rollup_original_budget
783                ,rollup_earned_amt
784                ,rollup_paid_amt
785                -- yzhao 10/14/2003 added below
786                ,committed_amt
787                ,recal_committed
788                ,rollup_committed_amt
789                ,rollup_recal_committed
790                ,plan_id
791                ,NVL(liability_flag, 'N')
792                -- yzhao: 11.5.10
793                ,utilized_amt
794                ,rollup_utilized_amt
795          FROM ozf_funds_all_b
796          WHERE fund_id = p_fund_id;
797 
798       /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
799       CURSOR c_mc_trans(p_fund_id IN NUMBER) IS
800          SELECT mc_record_id
801                 ,object_version_number
802                 ,amount_column1 -- original
803                 ,amount_column6 -- committed; yzhao: 10/14/2003 added
804                 ,amount_column7 -- earn
805                 ,amount_column8 -- paid
806         ,amount_column9 -- utilized
807          FROM ozf_mc_transactions_all
808          WHERE source_object_name ='FUND'
809          AND source_object_id = p_fund_id;
810        */
811 
812       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
813          SELECT offer_type, custom_setup_id, beneficiary_account_id, transaction_currency_code,offer_id
814                  ,autopay_party_attr,autopay_party_id --nirprasa
815          FROM   ozf_offers
816          WHERE  qp_list_header_id = p_offer_id;
817 
818       CURSOR c_accrual_flag (p_price_adjustment_id IN NUMBER) IS
819          SELECT NVL(accrual_flag,'N')
820          FROM oe_price_adjustments
821          WHERE price_Adjustment_id = p_price_Adjustment_id;
822 
823       CURSOR c_parent (p_fund_id IN NUMBER)IS
824          SELECT fund_id
825                ,object_version_number
826                ,rollup_original_budget
827                ,rollup_earned_amt
828                ,rollup_paid_amt
829                -- yzhao: 10/14/2003 added
830                ,rollup_committed_amt
831                ,rollup_recal_committed
832                -- yzhao: 11.5.10
833                ,rollup_utilized_amt
834          FROM ozf_funds_all_b
835          connect by prior  parent_fund_id =fund_id
836          start with fund_id =  p_fund_id;
837 
838       /* 10/14/2003  yzhao  Fix TEVA bug - customer fully accrual budget committed amount is always 0
839                        update ozf_act_budgets REQUEST between fully accrual budget and its offer when accrual happens
840        */
841       CURSOR c_accrual_budget_reqeust(p_fund_id IN NUMBER, p_plan_id IN NUMBER) IS
842          SELECT activity_budget_id
843              , object_version_number
844          FROM   ozf_act_budgets
845          WHERE  arc_act_budget_used_by = 'OFFR'
846          AND    act_budget_used_by_id = p_plan_id
847          AND    budget_source_type = 'FUND'
848          AND    budget_source_id = p_fund_id
849          AND    transfer_type = 'REQUEST'
850          AND    status_code = 'APPROVED';
851 
852       CURSOR c_budget_request_utilrec(p_fund_id IN NUMBER, p_plan_id IN NUMBER, p_actbudget_id IN NUMBER) IS
853          SELECT utilization_id
854                 , object_version_number
855          FROM   ozf_funds_utilized_all_b
856          WHERE  utilization_type = 'REQUEST'
857          AND    fund_id = p_fund_id
858          AND    plan_type = 'FUND'
859          AND    plan_id = p_fund_id
860          AND    component_type = 'OFFR'
861          AND    component_id = p_plan_id
862          AND    ams_activity_budget_id = p_actbudget_id;
863 
864      /*fix for bug 4778995
865      -- yzhao: 11.5.10 get time_id
866      CURSOR c_get_time_id(p_date IN DATE) IS
867         SELECT month_id, ent_qtr_id, ent_year_id
868         FROM   ozf_time_day
869         WHERE  report_date = trunc(p_date);
870      */
871 
872 
873      /* Add by feliu on 12/30/03 to fix org issue:
874         If order org's SOB is different than Budget Org's SOB, then we use Budget's org_id and function currency.
875     and have log message to ask use to make manual adjustment.otherwise we use order org_id and function currency.
876       kdass 08/23/2005 MOAC change: changed comparison from SOB to Ledger
877       */
878       /*
879       CURSOR c_order_sob(p_org_id IN NUMBER) IS
880         SELECT SET_OF_BOOKS_ID
881         FROM ozf_sys_parameters_all
882         WHERE org_id = p_org_id;
883 
884       -- yzhao: 11.5.10 check if post to gl for off invoice discount
885       CURSOR c_fund_sob(p_fund_id IN NUMBER) IS
886         SELECT  sob.set_of_books_id, fun.ORG_id, NVL(sob.gl_acct_for_offinv_flag, 'F')
887         FROM    ozf_sys_parameters_all sob
888                ,ozf_funds_all_b  fun
889         WHERE fun.fund_id = p_fund_id
890         AND   sob.org_id = fun.ORG_id ;
891       */
892 
893       CURSOR c_fund_ledger(p_fund_id IN NUMBER) IS
894          SELECT  fun.ledger_id
895          FROM    ozf_sys_parameters_all sob
896                ,ozf_funds_all_b fun
897          WHERE fun.fund_id = p_fund_id
898          AND   sob.org_id = fun.org_id;
899 
900       CURSOR c_offinv_flag(p_org_id IN NUMBER) IS
901          SELECT  NVL(sob.gl_acct_for_offinv_flag, 'F')
902          FROM    ozf_sys_parameters_all sob
903          WHERE   sob.org_id = p_org_id;
904 
905       -- yzhao: 11.5.10 populate reference_type/id for special pricing
906       CURSOR c_get_request_header_id(p_list_header_id IN NUMBER) IS
907          SELECT request_header_id
908          FROM   ozf_request_headers_all_b
909          WHERE  offer_id =p_list_header_id;
910 
911      -- rimehrot: for R12 update ozf_object_fund_summary table
912       CURSOR c_get_objfundsum_rec(p_object_type IN VARCHAR2, p_object_id IN NUMBER, p_fund_id IN NUMBER) IS
913          SELECT objfundsum_id
914               , object_version_number
915               , committed_amt
916               , recal_committed_amt
917               , utilized_amt
918               , earned_amt
919               , paid_amt
920               , plan_curr_committed_amt
921               , plan_curr_recal_committed_amt
922               , plan_curr_utilized_amt
923               , plan_curr_earned_amt
924               , plan_curr_paid_amt
925               , univ_curr_committed_amt
926               , univ_curr_recal_committed_amt
927               , univ_curr_utilized_amt
928               , univ_curr_earned_amt
929               , univ_curr_paid_amt
930          FROM   ozf_object_fund_summary
931          WHERE  object_type = p_object_type
932          AND    object_id = p_object_id
933          AND    fund_id = p_fund_id;
934 
935 --Ship - Debit Enhancements / Added by Pranay
936       CURSOR c_sd_request_header_id(p_list_header_id IN NUMBER) IS
937          SELECT request_header_id
938          FROM   ozf_sd_request_headers_all_b
939          WHERE  offer_id =p_list_header_id;
940 
941 -- nirprasa, cursor for currency conversion type.
942       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
943          SELECT exchange_rate_type
944          FROM   ozf_sys_parameters_all
945          WHERE  org_id = p_org_id;
946 
947    BEGIN
948       --------------------- initialize -----------------------
949       SAVEPOINT create_utilized_rec;
950       IF g_debug_flag = 'Y' THEN
951          ozf_utility_pvt.write_conc_log(   l_full_name
952                                      || ': start' || p_utilization_rec.utilization_type);
953       END IF;
954 
955       x_return_status            := fnd_api.g_ret_sts_success;
956 
957        -- Get the identifier
958       OPEN c_utilization_seq;
959       FETCH c_utilization_seq INTO l_utilization_rec.utilization_id;
960       CLOSE c_utilization_seq;
961       OPEN c_fund_b (l_utilization_rec.fund_id);
962       FETCH c_fund_b INTO l_obj_num
963                          ,l_accrual_basis
964                          ,l_fund_type
965                          ,l_original_budget
966                          ,l_earned_amt
967                          ,l_paid_amt
968                          ,l_parent_fund_id
969                          ,l_rollup_orig_amt
970                          ,l_rollup_earned_amt
971                          ,l_rollup_paid_amt
972                          ,l_committed_amt
973                          ,l_recal_committed
974                          ,l_rollup_committed_amt
975                          ,l_rollup_recal_committed
976                          ,l_plan_id
977                          ,l_liability_flag
978                          ,l_utilized_amt
979                          ,l_rollup_utilized_amt;
980       IF (c_fund_b%NOTFOUND) THEN
981          CLOSE c_fund_b;
982          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
983             fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
984             fnd_msg_pub.ADD;
985          END IF;
986          RAISE fnd_api.g_exc_error;
987       END IF;
988       CLOSE c_fund_b;
989 
990       OPEN c_offinv_flag(l_utilization_rec.org_id);
991       FETCH c_offinv_flag INTO l_off_invoice_gl_post_flag;
992       CLOSE c_offinv_flag;
993 
994       --kdass MOAC changes: change comparison from SOB to Ledger
995       /*
996       OPEN c_order_sob(l_utilization_rec.org_id);
997       FETCH c_order_sob INTO l_order_sob;
998       CLOSE c_order_sob;
999 
1000       OPEN c_fund_sob(l_utilization_rec.fund_id);
1001       FETCH c_fund_sob INTO l_fund_sob, l_fund_org, l_off_invoice_gl_post_flag;
1002       CLOSE c_fund_sob;
1003       */
1004 
1005       OPEN c_fund_ledger(l_utilization_rec.fund_id);
1006       FETCH c_fund_ledger INTO l_fund_ledger;
1007       CLOSE c_fund_ledger;
1008       --get the order's ledger id
1009       mo_utils.Get_Ledger_Info (p_operating_unit => l_utilization_rec.org_id
1010                                ,p_ledger_id      => l_order_ledger
1011                                ,p_ledger_name    => l_ord_ledger_name);
1012       IF l_utilization_rec.org_id IS NULL THEN
1013          IF g_debug_flag = 'Y' THEN
1014             ozf_utility_pvt.write_conc_log (' org_id from order is null ');
1015          END IF;
1016       ELSE
1017          IF g_debug_flag = 'Y' THEN
1018             ozf_utility_pvt.write_conc_log (' org_id from order: ' || l_utilization_rec.org_id);
1019          END IF;
1020       END IF;
1021 
1022       IF l_fund_ledger IS NOT NULL AND l_order_ledger <> l_fund_ledger THEN
1023          -- l_utilization_rec.org_id := l_fund_org;  R12: stick to order's org. Budget org is not essential information
1024          ozf_utility_pvt.write_conc_log (' Warning: There is a potential problem with this accrual record. The ledger ');
1025          ozf_utility_pvt.write_conc_log ('used by Trade Management to create the GL postings for this ');
1026          ozf_utility_pvt.write_conc_log ('accrual does not match the one the sales order rolls up to. Please ');
1027          ozf_utility_pvt.write_conc_log ('review carefully and make adjustments in Trade Management if necessary.');
1028       END IF;
1029 
1030       -- Added for bug 7030415, moved the the code here to get the correct utilization org_id.
1031 
1032       OPEN c_offer_type(l_utilization_rec.component_id);
1033       FETCH c_offer_type INTO l_offer_type, l_custom_setup_id, l_beneficiary_account_id, l_plan_currency,l_offer_id,
1034                               l_autopay_party_attr,l_autopay_party_id;
1035       CLOSE c_offer_type;
1036 
1037       -- added by feliu on 08/30/2005 for R12.
1038       IF l_offer_type = 'VOLUME_OFFER' THEN
1039          l_beneficiary_account_id := ozf_volume_calculation_pub.get_beneficiary(l_offer_id
1040                                                                             ,l_utilization_rec.billto_cust_account_id);
1041       END IF;
1042 
1043       -- yzhao: 11.5.10 populate cust_account_id with offer's beneficiary account, otherwise billto cust account id
1044 
1045 
1046         IF l_utilization_rec.cust_account_id IS NULL THEN
1047          IF l_beneficiary_account_id IS NOT NULL THEN
1048 
1049             --Added c_site_org_id for bug 6278466
1050             IF l_autopay_party_attr <> 'CUSTOMER' THEN
1051               OPEN c_site_org_id(l_autopay_party_id);
1052               FETCH c_site_org_id INTO l_org_id;
1053               CLOSE c_site_org_id;
1054               l_utilization_rec.org_id := l_org_id;
1055             END IF;
1056 
1057 	    l_utilization_rec.cust_account_id := l_beneficiary_account_id;
1058 
1059             --kdass bug 8258508/ Duplicate bill to sites for same cust_account_id. Cases are as follows:
1060 	    --Defaulting bill_to_site_id from beneficiary of type CUSTOMER_BILL_TO
1061 	    --Defaulting ship_to from beneficiary of type SHIP_TO
1062 	    --No bill_to/ship_to for beneficiary of type CUSTOMER
1063             IF l_autopay_party_attr = 'CUSTOMER_BILL_TO' THEN
1064                 l_utilization_rec.bill_to_site_use_id := l_autopay_party_id;
1065 		l_utilization_rec.ship_to_site_use_id := NULL;
1066             ELSIF l_autopay_party_attr = 'SHIP_TO' THEN
1067 	        l_utilization_rec.bill_to_site_use_id := NULL;
1068 		l_utilization_rec.ship_to_site_use_id := l_autopay_party_id;
1069 	    ELSIF l_autopay_party_attr = 'CUSTOMER' THEN
1070                 l_utilization_rec.bill_to_site_use_id := NULL;
1071 		l_utilization_rec.ship_to_site_use_id := NULL;
1072             END IF;
1073 
1074             IF g_debug_flag = 'Y' THEN
1075                ozf_utility_pvt.write_conc_log ('l_utilization_rec.bill_to_site_use_id: ' || l_utilization_rec.bill_to_site_use_id);
1076 	       ozf_utility_pvt.write_conc_log ('l_utilization_rec.ship_to_site_use_id: ' || l_utilization_rec.ship_to_site_use_id);
1077             END IF;
1078 
1079          ELSE
1080             l_utilization_rec.cust_account_id := l_utilization_rec.billto_cust_account_id;
1081          END IF;
1082         END IF;
1083 
1084 
1085         /* Added for bug 7030415,- get the exchange rate based on org_id and pass it to the currency conversion API
1086         Utilization amount is converted from utilization curr to functional curr to populate
1087         acctd_amount column of utilization table.*/
1088 
1089 
1090         OPEN c_get_conversion_type(l_utilization_rec.org_id);
1091         FETCH c_get_conversion_type INTO l_utilization_rec.exchange_rate_type;
1092         CLOSE c_get_conversion_type;
1093 
1094       IF l_utilization_rec.amount <> 0 THEN
1095          l_utilization_rec.amount := ozf_utility_pvt.currround(l_utilization_rec.amount , l_utilization_rec.currency_code);  -- round amount to fix bug 3615680;
1096 
1097          IF g_debug_flag = 'Y' THEN
1098           ozf_utility_pvt.write_conc_log('**************************START****************************');
1099           ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_utilization_rec.amount );
1100           ozf_utility_pvt.write_conc_log(l_api_name||' From Curr: '||l_utilization_rec.currency_code );
1101           ozf_utility_pvt.write_conc_log(l_api_name||' p_ledger_id: '|| l_order_ledger);
1102           ozf_utility_pvt.write_conc_log(l_api_name||' l_utilization_rec.exchange_rate_type: '|| l_utilization_rec.exchange_rate_type);
1103           ozf_utility_pvt.write_conc_log('Utilization amount is converted from utilization curr to functional curr to populate acctd_amount column');
1104         END IF;
1105          ozf_utility_pvt.calculate_functional_currency (
1106                   p_from_amount=> l_utilization_rec.amount
1107                  ,p_tc_currency_code=> l_utilization_rec.currency_code
1108                  ,p_ledger_id => l_order_ledger
1109                  ,x_to_amount=> l_utilization_rec.acctd_amount
1110                  ,x_mrc_sob_type_code=> l_sob_type_code
1111                  ,x_fc_currency_code=> l_fc_code
1112                  ,x_exchange_rate_type=> l_utilization_rec.exchange_rate_type
1113                  ,x_exchange_rate=> l_utilization_rec.exchange_rate
1114                  ,x_return_status=> l_return_status
1115                );
1116 
1117          IF l_return_status = fnd_api.g_ret_sts_error THEN
1118             RAISE fnd_api.g_exc_error;
1119          ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1120             RAISE fnd_api.g_exc_unexpected_error;
1121          END IF;
1122       END IF;
1123 
1124       -- yzhao: 10/20/2003 when object sources from sales accrual budget, the budget behaves like fixed budget.
1125       IF l_fund_type = 'FULLY_ACCRUED' AND
1126          l_utilization_rec.component_type = 'OFFR' AND
1127          l_plan_id <> l_utilization_rec.component_id  THEN
1128          l_fund_type := 'FIXED' ;
1129       END IF;
1130 
1131 
1132       IF l_fund_type = 'FIXED' THEN
1133       ---- kpatro 11/09/2006 added check for utilization_type to fix 5523042
1134       IF  l_utilization_rec.utilization_type IS NULL THEN
1135          IF l_offer_type IN ('ACCRUAL') THEN
1136             l_utilization_rec.utilization_type := 'ACCRUAL';
1137             l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1138             l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1139             l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1140          ELSIF l_offer_type IN( 'DEAL','VOLUME_OFFER') THEN
1141             l_accrual_flag :='N';
1142             OPEN c_accrual_flag( l_utilization_rec.price_adjustment_id ) ;
1143             FETCH c_accrual_flag INTO l_accrual_flag ;
1144             CLOSE c_accrual_flag ;
1145             IF l_accrual_flag = 'Y' THEN
1146                l_utilization_rec.utilization_type := 'ACCRUAL';
1147                l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1148                l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1149                l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1150             ELSE
1151                l_utilization_rec.utilization_type := 'UTILIZED';
1152             END IF;
1153          ELSE
1154             l_utilization_rec.utilization_type := 'UTILIZED';
1155          END IF;
1156         END IF;
1157          -- 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
1158          --          if flag is on, leave the flag as 'N'
1159          IF l_utilization_rec.utilization_type = 'UTILIZED'
1160          --AND l_off_invoice_gl_post_flag = 'F'
1161          THEN
1162            -- l_utilization_rec.gl_posted_flag := G_GL_FLAG_NULL;  -- null;
1163          --ELSE
1164             IF l_utilization_rec.gl_posted_flag IS NULL THEN  -- added by feliu on 06/09/04
1165                l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;      -- 'N', waiting for posting to gl
1166             END IF;
1167 
1168             IF l_utilization_rec.gl_posted_flag = G_GL_FLAG_NO
1169             AND l_utilization_rec.utilization_type IN ( 'ACCRUAL' ,'ADJUSTMENT') THEN
1170                l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1171                l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1172                l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1173             END IF;
1174          END IF;
1175       ELSE
1176          IF l_accrual_basis = 'SALES' THEN
1177             l_utilization_rec.utilization_type := 'SALES_ACCRUAL';
1178             l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;-- set to 'X' only after shipping.
1179          ELSIF l_accrual_basis = 'CUSTOMER' THEN
1180             l_utilization_rec.utilization_type := 'ACCRUAL';
1181             -- yzhao: fix bug 3435420 - do not post to gl for customer accrual budget with liability off
1182             IF l_liability_flag = 'Y' THEN
1183                l_utilization_rec.amount_remaining := l_utilization_rec.amount;
1184                l_utilization_rec.acctd_amount_remaining := l_utilization_rec.acctd_amount;
1185                l_utilization_rec.plan_curr_amount_remaining := l_utilization_rec.plan_curr_amount ;
1186                IF l_utilization_rec.gl_posted_flag IS NULL THEN  -- yzhao 06/10/04
1187                    l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;      -- 'N', waiting for posting to gl
1188                END IF;
1189             ELSE
1190                l_utilization_rec.gl_posted_flag := G_GL_FLAG_NO;--G_GL_FLAG_NOLIAB;  -- 'X', do not post to gl
1191             END IF;
1192          END IF;
1193       END IF;
1194 
1195       l_utilization_rec.plan_id       := l_utilization_rec.component_id;
1196       l_utilization_rec.plan_type       := 'OFFR';
1197       l_utilization_rec.component_type       := 'OFFR';
1198       l_utilization_rec.adjustment_desc := fnd_message.get_string ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK');
1199 
1200       -- yzhao: 11/25/2003 11.5.10 populate adjustment_date and time_id
1201       IF l_utilization_rec.adjustment_date IS NULL THEN
1202          l_utilization_rec.adjustment_date := SYSDATE;
1203       END IF;
1204 
1205       /*fix for bug 4778995
1206       OPEN c_get_time_id(l_utilization_rec.adjustment_date);
1207       FETCH c_get_time_id INTO l_utilization_rec.month_id, l_utilization_rec.quarter_id, l_utilization_rec.year_id;
1208       CLOSE c_get_time_id;
1209       */
1210 
1211 
1212       /* yzhao: 11.5.10 populate reference_type/id for special pricing
1213                 seeded custom_setup_id for special pricing:
1214                 115 offer invoice
1215                 116 accrual
1216                 117 scan data
1217       */
1218       IF l_utilization_rec.reference_id IS NULL AND l_custom_setup_id IN (115, 116, 117) THEN
1219          OPEN c_get_request_header_id(l_utilization_rec.component_id);
1220          FETCH c_get_request_header_id INTO l_utilization_rec.reference_id;
1221          CLOSE c_get_request_header_id;
1222          l_utilization_rec.reference_type := 'SPECIAL_PRICE';
1223       END IF;
1224 
1225       --Ship - Debit enhancements / Added by Pranay
1226       IF l_utilization_rec.reference_id IS NULL AND l_custom_setup_id = 118 THEN
1227          OPEN c_sd_request_header_id(l_utilization_rec.component_id);
1228          FETCH c_sd_request_header_id INTO l_utilization_rec.reference_id;
1229          CLOSE c_sd_request_header_id;
1230          l_utilization_rec.reference_type := 'SD_REQUEST';
1231       END IF;
1232 
1233       --feliu, add on 07/30/04 to populate adjustment if adjust_type_id is not null
1234       IF l_utilization_rec.adjustment_type_id IS NOT NULL THEN
1235            l_utilization_rec.utilization_type := 'ADJUSTMENT';
1236       END IF;
1237 
1238        --rimehrot for R12, if gl_posted_flag = Y or Null and gl_date is null, make gl_date = adjustment_date
1239       IF l_utilization_rec.gl_date IS NULL THEN
1240         IF l_utilization_rec.gl_posted_flag IS NULL OR l_utilization_rec.gl_posted_flag = G_GL_FLAG_YES THEN
1241           l_utilization_rec.gl_date := l_utilization_rec.adjustment_date;
1242         END IF;
1243       END IF;
1244 
1245       --get amount for universal currency and used to update rollup amount.
1246       IF g_universal_currency IS NULL THEN
1247          IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error) THEN
1248             fnd_message.set_name('OZF', 'OZF_UNIV_CURR_NOT_FOUND');
1249             fnd_msg_pub.add;
1250          END IF;
1251             RAISE fnd_api.g_exc_error;
1252       END IF;
1253 
1254       --rimehrot for R12, populate universal currency amount column
1255       IF g_universal_currency = l_utilization_rec.currency_code THEN
1256          l_utilization_rec.univ_curr_amount := l_utilization_rec.amount;
1257          l_utilization_rec.univ_curr_amount_remaining := l_utilization_rec.amount_remaining;
1258       ELSIF g_universal_currency = l_plan_currency THEN
1259          l_utilization_rec.univ_curr_amount := l_utilization_rec.plan_curr_amount;
1260          l_utilization_rec.univ_curr_amount_remaining := l_utilization_rec.plan_curr_amount_remaining;
1261       ELSE
1262          /*Added for bug 7030415 - Send the exchange rate
1263         Utilization amount is converted from request curr to universal curr to populate univ_curr_amount
1264         column in ozf_funds_utilized_all_b */
1265 
1266         IF g_debug_flag = 'Y' THEN
1267          ozf_utility_pvt.write_conc_log('**************************START****************************');
1268          ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_utilization_rec.amount );
1269          ozf_utility_pvt.write_conc_log(l_api_name||' From Curr: '||l_utilization_rec.currency_code );
1270          ozf_utility_pvt.write_conc_log(l_api_name||' to curr univ_curr_amount: '|| g_universal_currency);
1271          ozf_utility_pvt.write_conc_log(l_api_name||' l_exchange_rate_type: '|| l_utilization_rec.exchange_rate_type);
1272         END IF;
1273          ozf_utility_pvt.convert_currency (
1274                    p_from_currency=> l_utilization_rec.currency_code
1275                   ,p_to_currency=> g_universal_currency
1276                   ,p_conv_type=> l_utilization_rec.exchange_rate_type --Added for bug 7030415
1277                   ,p_from_amount=> l_utilization_rec.amount
1278                   ,x_return_status=> l_return_status
1279                   ,x_to_amount=> l_utilization_rec.univ_curr_amount
1280                   ,x_rate=> l_rate
1281                 );
1282          IF g_debug_flag = 'Y' THEN
1283           ozf_utility_pvt.write_conc_log(l_api_name||' Converted Amount l_utilization_rec.univ_curr_amount: '|| l_utilization_rec.univ_curr_amount);
1284           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');
1285          END IF;
1286          IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1287             RAISE fnd_api.g_exc_unexpected_error;
1288          ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
1289             RAISE fnd_api.g_exc_error;
1290          END IF;
1291          /* Send the exchange rate for bug 7030415 */
1292          ozf_utility_pvt.convert_currency (
1293                    p_from_currency=> l_utilization_rec.currency_code
1294                   ,p_to_currency=> g_universal_currency
1295                   ,p_conv_type=> l_utilization_rec.exchange_rate_type --Added for bug 7030415
1296                   ,p_from_amount=> l_utilization_rec.amount_remaining
1297                   ,x_return_status=> l_return_status
1298                   ,x_to_amount=> l_utilization_rec.univ_curr_amount_remaining
1299                   ,x_rate=> l_rate
1300                 );
1301          IF g_debug_flag = 'Y' THEN
1302            ozf_utility_pvt.write_conc_log(l_api_name||' From Amount: '||l_utilization_rec.amount_remaining );
1303            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);
1304            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');
1305            ozf_utility_pvt.write_conc_log('***************************END******************************');
1306          END IF;
1307          IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1308             RAISE fnd_api.g_exc_unexpected_error;
1309          ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
1310             RAISE fnd_api.g_exc_error;
1311          END IF;
1312       END IF; -- g_universal_currency = l_utilization_rec.currency_code
1313 
1314       INSERT INTO ozf_funds_utilized_all_b
1315                      (utilization_id,last_update_date
1316                      ,last_updated_by,last_update_login
1317                      ,creation_date,created_by
1318                      ,created_from,request_id
1319                      ,program_application_id,program_id
1320                      ,program_update_date,utilization_type
1321                      ,fund_id,plan_type
1322                      ,plan_id,component_type,component_id
1323                      ,object_type,object_id
1324                      ,order_id,invoice_id
1325                      ,amount,acctd_amount
1326                      ,currency_code,exchange_rate_type
1327                      ,exchange_rate_date,exchange_rate
1328                      ,adjustment_type,adjustment_date
1329                      ,object_version_number,attribute_category
1330                      ,attribute1,attribute2
1331                      ,attribute3,attribute4
1332                      ,attribute5,attribute6
1333                      ,attribute7,attribute8
1334                      ,attribute9,attribute10
1335                      ,attribute11,attribute12
1336                      ,attribute13,attribute14
1337                      ,attribute15,org_id
1338                      ,adjustment_type_id,camp_schedule_id
1339                      ,gl_date, gl_posted_flag
1340                      ,product_level_type
1341                      ,product_id,ams_activity_budget_id
1342                      ,amount_remaining,acctd_amount_remaining
1343                      ,cust_account_id,price_adjustment_id
1344                      ,plan_curr_amount,plan_curr_amount_remaining
1345                      ,scan_unit,scan_unit_remaining
1346                      ,activity_product_id,volume_offer_tiers_id
1347                      --  11/04/2003   yzhao     11.5.10: added
1348                      ,billto_cust_account_id
1349                      ,reference_type
1350                      ,reference_id
1351                      /*fix for bug 4778995
1352                      ,month_id
1353                      ,quarter_id
1354                      ,year_id
1355                      */
1356                      ,order_line_id
1357                      ,orig_utilization_id -- added by feliu on 08/03/04
1358                      -- added by rimehrot for R12
1359                      ,bill_to_site_use_id
1360                      ,ship_to_site_use_id
1361                      ,univ_curr_amount
1362                      ,univ_curr_amount_remaining
1363         )
1364               VALUES (l_utilization_rec.utilization_id,SYSDATE -- LAST_UPDATE_DATE
1365                      ,NVL (fnd_global.user_id, -1),NVL (fnd_global.conc_login_id, -1) -- LAST_UPDATE_LOGIN
1366                      ,SYSDATE,NVL (fnd_global.user_id, -1) -- CREATED_BY
1367                      ,l_utilization_rec.created_from,fnd_global.conc_request_id -- REQUEST_ID
1368                      ,fnd_global.prog_appl_id,fnd_global.conc_program_id -- PROGRAM_ID
1369                      ,SYSDATE,l_utilization_rec.utilization_type
1370                      ,l_utilization_rec.fund_id,l_utilization_rec.plan_type
1371                      ,l_utilization_rec.plan_id,l_utilization_rec.component_type
1372                      ,l_utilization_rec.component_id,l_utilization_rec.object_type
1373                      ,l_utilization_rec.object_id,l_utilization_rec.order_id
1374                      ,l_utilization_rec.invoice_id,l_utilization_rec.amount
1375                      ,l_utilization_rec.acctd_amount,l_utilization_rec.currency_code
1376                      ,l_utilization_rec.exchange_rate_type,SYSDATE
1377                      ,l_utilization_rec.exchange_rate,l_utilization_rec.adjustment_type
1378                      ,l_utilization_rec.adjustment_date,1 -- object_version_number
1379                      ,l_utilization_rec.attribute_category,l_utilization_rec.attribute1
1380                      ,l_utilization_rec.attribute2
1381                      ,l_utilization_rec.attribute3,l_utilization_rec.attribute4
1382                      ,l_utilization_rec.attribute5,l_utilization_rec.attribute6
1383                      ,l_utilization_rec.attribute7,l_utilization_rec.attribute8
1384                      ,l_utilization_rec.attribute9,l_utilization_rec.attribute10
1385                      ,l_utilization_rec.attribute11,l_utilization_rec.attribute12
1386                      ,l_utilization_rec.attribute13,l_utilization_rec.attribute14
1387                      ,l_utilization_rec.attribute15,l_utilization_rec.org_id--TO_NUMBER (SUBSTRB (USERENV ('CLIENT_INFO'), 1, 10)) -- org_id
1388                      ,l_utilization_rec.adjustment_type_id,l_utilization_rec.camp_schedule_id
1389                      ,l_utilization_rec.gl_date, l_utilization_rec.gl_posted_flag
1390                      ,l_utilization_rec.product_level_type
1391                      ,l_utilization_rec.product_id,l_utilization_rec.ams_activity_budget_id
1392                      ,l_utilization_rec.amount_remaining,l_utilization_rec.acctd_amount_remaining
1393                      ,l_utilization_rec.cust_account_id,l_utilization_rec.price_adjustment_id
1394                      ,l_utilization_rec.plan_curr_amount,l_utilization_rec.plan_curr_amount_remaining
1395                      ,l_utilization_rec.scan_unit,l_utilization_rec.scan_unit_remaining
1396                      ,l_utilization_rec.activity_product_id,l_utilization_rec.volume_offer_tiers_id
1397                      --  11/04/2003   yzhao     11.5.10: added
1398                      ,l_utilization_rec.billto_cust_account_id
1399                      ,l_utilization_rec.reference_type
1400                      ,l_utilization_rec.reference_id
1401                      /*fix for bug 4778995
1402                      ,l_utilization_rec.month_id
1403                      ,l_utilization_rec.quarter_id
1404                      ,l_utilization_rec.year_id
1405                      */
1406                      ,l_utilization_rec.order_line_id
1407                      ,l_utilization_rec.orig_utilization_id
1408                      -- added by rimehrot for R12
1409                     ,l_utilization_rec.bill_to_site_use_id
1410                     ,l_utilization_rec.ship_to_site_use_id
1411                     ,l_utilization_rec.univ_curr_amount
1412                     ,l_utilization_rec.univ_curr_amount_remaining
1413              );
1414 
1415          INSERT INTO ozf_funds_utilized_all_tl
1416                      (utilization_id,last_update_date
1417                      ,last_updated_by,last_update_login
1418                      ,creation_date,created_by
1419                      ,created_from,request_id
1420                      ,program_application_id,program_id
1421                      ,program_update_date,adjustment_desc
1422                      ,source_lang,language
1423                      ,org_id
1424                      )
1425             SELECT l_utilization_rec.utilization_id
1426                   ,SYSDATE -- LAST_UPDATE_DATE
1427                   ,NVL (fnd_global.user_id, -1) -- LAST_UPDATED_BY
1428                   ,NVL (fnd_global.conc_login_id, -1) -- LAST_UPDATE_LOGIN
1429                   ,SYSDATE -- CREATION_DATE
1430                   ,NVL (fnd_global.user_id, -1) -- CREATED_BY
1431                   ,l_utilization_rec.created_from -- CREATED_FROM
1432                   ,fnd_global.conc_request_id -- REQUEST_ID
1433                   ,fnd_global.prog_appl_id -- PROGRAM_APPLICATION_ID
1434                   ,fnd_global.conc_program_id -- PROGRAM_ID
1435                   ,SYSDATE -- PROGRAM_UPDATE_DATE
1436                   ,l_utilization_rec.adjustment_desc -- ADJUSTMENT_DESCRIPTION
1437                   ,USERENV ('LANG') -- SOURCE_LANGUAGE
1438                   ,l.language_code -- LANGUAGE
1439                   ,l_utilization_rec.org_id --TO_NUMBER (SUBSTRB (USERENV ('CLIENT_INFO'), 1, 10)) -- org_id
1440               FROM fnd_languages l
1441               WHERE l.installed_flag IN ('I', 'B')
1442               AND NOT EXISTS ( SELECT NULL
1443                                   FROM ozf_funds_utilized_all_tl t
1444                                  WHERE t.utilization_id = l_utilization_rec.utilization_id
1445                                    AND t.language = l.language_code);
1446 
1447          x_utilization_id :=       l_utilization_rec.utilization_id  ;
1448 
1449          IF l_utilization_rec.utilization_type IN ('ACCRUAL', 'SALES_ACCRUAL', 'UTILIZED', 'ADJUSTMENT') THEN
1450             /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
1451                 OPEN c_mc_trans (l_utilization_rec.fund_id);
1452                 FETCH c_mc_trans INTO l_mc_record_id
1453                                      ,l_mc_obj_num
1454                                      ,l_mc_col_1
1455                                      ,l_mc_col_6        -- yzhao: 10/14/2003 added
1456                                      ,l_mc_col_7
1457                                      ,l_mc_col_8
1458                      ,l_mc_col_9;
1459                 IF (c_mc_trans%NOTFOUND) THEN
1460                    CLOSE c_mc_trans;
1461                    IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1462                       fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1463                       fnd_msg_pub.ADD;
1464                    END IF;
1465                    RAISE fnd_api.g_exc_error;
1466                 END IF;
1467                 CLOSE c_mc_trans;
1468             */
1469                -- rimehrot changed for R12, Populate new table ozf_object_fund_summary
1470                -- rimehrot: component_id/type is the destination. Will always be equal to plan_id/type in this case
1471             l_objfundsum_rec := NULL;
1472             OPEN c_get_objfundsum_rec(l_utilization_rec.component_type
1473                                      , l_utilization_rec.component_id
1474                                      , l_utilization_rec.fund_id);
1475             FETCH c_get_objfundsum_rec INTO l_objfundsum_rec.objfundsum_id
1476                                            , l_objfundsum_rec.object_version_number
1477                                            , l_objfundsum_rec.committed_amt
1478                                            , l_objfundsum_rec.recal_committed_amt
1479                                            , l_objfundsum_rec.utilized_amt
1480                                            , l_objfundsum_rec.earned_amt
1481                                            , l_objfundsum_rec.paid_amt
1482                                            , l_objfundsum_rec.plan_curr_committed_amt
1483                                            , l_objfundsum_rec.plan_curr_recal_committed_amt
1484                                            , l_objfundsum_rec.plan_curr_utilized_amt
1485                                            , l_objfundsum_rec.plan_curr_earned_amt
1486                                            , l_objfundsum_rec.plan_curr_paid_amt
1487                                            , l_objfundsum_rec.univ_curr_committed_amt
1488                                            , l_objfundsum_rec.univ_curr_recal_committed_amt
1489                                            , l_objfundsum_rec.univ_curr_utilized_amt
1490                                            , l_objfundsum_rec.univ_curr_earned_amt
1491                                            , l_objfundsum_rec.univ_curr_paid_amt;
1492             CLOSE c_get_objfundsum_rec;
1493 
1494             IF l_fund_type = 'FULLY_ACCRUED' THEN
1495                -- for a fully accrued customer fund with liability flag on, the budgeted, utilized and committed column gets populated
1496                -- 11.5.10: update utilized_amt, not earned_amt
1497                IF l_accrual_basis = 'CUSTOMER' AND NVL(l_liability_flag, 'N') = 'Y' THEN
1498                   l_original_budget := NVL (l_original_budget, 0)+ NVL (l_utilization_rec.amount, 0);
1499                   l_utilized_amt     := NVL (l_utilized_amt, 0)+ NVL (l_utilization_rec.amount, 0);
1500                   l_rollup_orig_amt :=NVL(l_rollup_orig_amt,0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1501                   l_rollup_utilized_amt := NVL(l_rollup_utilized_amt,0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1502                   -- l_mc_col_1     := NVL(l_mc_col_1,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1503                   -- l_mc_col_9     := NVL(l_mc_col_9,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1504                   l_new_orig_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1505                   l_new_utilized_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1506                   l_new_paid_amt := 0;
1507 
1508                  -- rimehrot changed for R12, Populate utilized/committed/recal_committed in ozf_object_fund_summary
1509                   l_objfundsum_rec.utilized_amt := NVL(l_objfundsum_rec.utilized_amt, 0) + NVL(l_utilization_rec.amount, 0);
1510                   l_objfundsum_rec.plan_curr_utilized_amt := NVL(l_objfundsum_rec.plan_curr_utilized_amt, 0)
1511                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1512                   l_objfundsum_rec.univ_curr_utilized_amt := NVL(l_objfundsum_rec.univ_curr_utilized_amt, 0)
1513                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1514                   l_objfundsum_rec.committed_amt := NVL(l_objfundsum_rec.committed_amt, 0) + NVL(l_utilization_rec.amount, 0);
1515                   l_objfundsum_rec.plan_curr_committed_amt := NVL(l_objfundsum_rec.plan_curr_committed_amt, 0)
1516                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1517                   l_objfundsum_rec.univ_curr_committed_amt := NVL(l_objfundsum_rec.univ_curr_committed_amt, 0)
1518                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1519                   l_objfundsum_rec.recal_committed_amt := NVL(l_objfundsum_rec.recal_committed_amt, 0)
1520                                                                   + NVL(l_utilization_rec.amount, 0);
1521                   l_objfundsum_rec.plan_curr_recal_committed_amt := NVL(l_objfundsum_rec.plan_curr_recal_committed_amt, 0)
1522                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1523                   l_objfundsum_rec.univ_curr_recal_committed_amt := NVL(l_objfundsum_rec.univ_curr_recal_committed_amt, 0)
1524                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1525                  -- rimehrot: end changes for R12
1526 
1527                   -- yzhao: 10/14/2003 Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
1528                   -- l_mc_col_6     := NVL(l_mc_col_6,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1529                   l_new_committed_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1530                   l_new_recal_committed := NVL (l_utilization_rec.univ_curr_amount, 0);
1531                   l_committed_amt := NVL(l_committed_amt, 0) + NVL (l_utilization_rec.amount, 0);
1532                   l_rollup_committed_amt := NVL(l_rollup_committed_amt, 0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1533                   l_recal_committed := NVL(l_recal_committed, 0) + NVL (l_utilization_rec.amount, 0);
1534                   l_rollup_recal_committed := NVL(l_rollup_recal_committed, 0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1535 
1536                   -- 10/14/2003  update ozf_act_budgets REQUEST between fully accrual budget and its offer when accrual happens
1537                   OPEN  c_accrual_budget_reqeust(l_utilization_rec.fund_id, l_plan_id);
1538                   FETCH c_accrual_budget_reqeust INTO l_act_budget_id, l_act_budget_objver;
1539                   IF (c_accrual_budget_reqeust%NOTFOUND) THEN
1540                      ozf_utility_pvt.write_conc_log ('    D: create_utilized_rec() ERROR customer fully accrual budget. can not find approved budget request record between fund '
1541                                      || l_utilization_rec.fund_id || ' and offer ' || l_plan_id);
1542                      CLOSE c_accrual_budget_reqeust;
1543                      IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1544                        fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1545                        fnd_msg_pub.ADD;
1546                      END IF;
1547                      RAISE fnd_api.g_exc_error;
1548                   END IF;
1549                   CLOSE c_accrual_budget_reqeust;
1550 
1551                   UPDATE ozf_act_budgets
1552                     SET    request_amount = NVL(request_amount, 0) + l_utilization_rec.plan_curr_amount
1553                           , src_curr_request_amt = NVL(src_curr_request_amt, 0) + l_utilization_rec.amount
1554                           , approved_amount = NVL(approved_amount, 0) + l_utilization_rec.plan_curr_amount
1555                           , approved_original_amount = NVL(approved_original_amount, 0) + l_utilization_rec.amount
1556                           , approved_amount_fc = NVL(approved_amount_fc, 0) + l_utilization_rec.acctd_amount
1557                           , last_update_date = sysdate
1558                           , last_updated_by = NVL (fnd_global.user_id, -1)
1559                           , last_update_login = NVL (fnd_global.conc_login_id, -1)
1560                           , object_version_number = l_act_budget_objver + 1
1561                   WHERE  activity_budget_id = l_act_budget_id
1562                   AND    object_version_number = l_act_budget_objver;
1563 
1564               -- 4619156, comment as request no longer in util table.
1565                /*   OPEN c_budget_request_utilrec(l_utilization_rec.fund_id, l_plan_id, l_act_budget_id);
1566                   FETCH c_budget_request_utilrec INTO l_act_budget_id, l_act_budget_objver;
1567                   IF (c_budget_request_utilrec%NOTFOUND) THEN
1568                       write_conc_log ('    D: create_utilized_rec() ERROR customer fully accrual budget. can not find approved budget request record in utilization table between fund '
1569                                       || l_utilization_rec.fund_id || ' and offer ' || l_plan_id);
1570                       CLOSE c_budget_request_utilrec;
1571                       IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1572                          fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
1573                          fnd_msg_pub.ADD;
1574                       END IF;
1575                       RAISE fnd_api.g_exc_error;
1576                   END IF;
1577                   CLOSE c_budget_request_utilrec;
1578 
1579                   -- populate request amount in ozf_funds_utilized_all_b record
1580                   UPDATE ozf_funds_utilized_all_b
1581                   SET    amount = NVL(amount,0) + NVL(l_utilization_rec.amount,0)
1582                        , plan_curr_amount = NVL(plan_curr_amount,0) + NVL(l_utilization_rec.plan_curr_amount,0)
1583                        , univ_curr_amount = NVL(univ_curr_amount, 0) + NVL(l_utilization_rec.univ_curr_amount, 0)
1584                        , acctd_amount = NVL(acctd_amount,0) + NVL(l_utilization_rec.acctd_amount,0)
1585                        , last_update_date = sysdate
1586                        , last_updated_by = NVL (fnd_global.user_id, -1)
1587                        , last_update_login = NVL (fnd_global.conc_login_id, -1)
1588                        , object_version_number = l_act_budget_objver + 1
1589                   WHERE  utilization_id = l_act_budget_id
1590                   AND    object_version_number = l_act_budget_objver;*/
1591                   -- yzhao: 10/14/2003 END Fix TEVA bug - customer fully accrual budget committed amount is always 0
1592 
1593                -- for a fully accrued sales fund and customer accrual with liability flag off,
1594                -- then only the budgeted column gets populated
1595                -- ELSIF l_accrual_basis = 'SALES' THEN
1596             /*  feliu1122
1597                ELSE
1598                   l_original_budget :=NVL (l_original_budget, 0)+ NVL (l_utilization_rec.amount, 0);
1599                   l_rollup_orig_amt :=NVL(l_rollup_orig_amt,0) + NVL (l_new_univ_amt, 0);
1600                   -- l_mc_col_1     := NVL(l_mc_col_1,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1601                   l_new_orig_amt := NVL (l_new_univ_amt, 0);
1602                   l_new_utilized_amt := 0;
1603                   l_new_paid_amt := 0;
1604 */             END IF;
1605             ELSE -- for fixed budget
1606                   -- utilized is always updated for Accrual or Utilized record
1607                l_utilized_amt      := NVL (l_utilized_amt, 0) + NVL (l_utilization_rec.amount, 0);
1608                l_rollup_utilized_amt := NVL(l_rollup_utilized_amt,0) + NVL (l_utilization_rec.univ_curr_amount, 0);
1609                l_new_utilized_amt := NVL (l_utilization_rec.univ_curr_amount, 0);
1610                   -- l_mc_col_9     := NVL(l_mc_col_9,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1611                   -- rimehrot: for R12, populate utilized amount
1612                l_objfundsum_rec.utilized_amt := NVL(l_objfundsum_rec.utilized_amt, 0) + NVL(l_utilization_rec.amount, 0);
1613                l_objfundsum_rec.plan_curr_utilized_amt := NVL(l_objfundsum_rec.plan_curr_utilized_amt, 0)
1614                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1615                l_objfundsum_rec.univ_curr_utilized_amt := NVL(l_objfundsum_rec.univ_curr_utilized_amt, 0)
1616                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1617 
1618                   -- end R12 changes
1619                   -- 11.5.10: for off-invoice offer, if posting to gl flag is off, utilized, eanred and paid updated the same time
1620                   --          if flag is on, only utilized will be updated, earned and paid will be updated after gl posting
1621                   --          fix bug 3428988 - for accrual offer, do not update paid and earned amount when creating utilization
1622                   /* feliu 1121
1623                   IF l_utilization_rec.utilization_type = 'UTILIZED' AND l_off_invoice_gl_post_flag = 'F' THEN
1624                      l_earned_amt      := NVL (l_earned_amt, 0) + NVL (l_utilization_rec.amount, 0);
1625                      l_rollup_earned_amt := NVL(l_rollup_earned_amt,0) + NVL (l_new_univ_amt, 0);
1626                      l_new_earned_amt := NVL (l_new_univ_amt, 0);
1627                      -- l_mc_col_7     := NVL(l_mc_col_7,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1628                      l_paid_amt      := NVL (l_paid_amt, 0) + NVL (l_utilization_rec.amount, 0);
1629                      l_rollup_paid_amt := NVL(l_rollup_paid_amt,0) + NVL (l_new_univ_amt, 0);
1630                      l_new_paid_amt := NVL (l_new_univ_amt, 0);
1631                      -- l_mc_col_8     := NVL(l_mc_col_8,0) +  NVL (l_utilization_rec.acctd_amount, 0);
1632                      -- rimehrot: for R12, populate earned/paid amount
1633                      l_objfundsum_rec.earned_amt := NVL(l_objfundsum_rec.earned_amt, 0) + NVL(l_utilization_rec.amount, 0);
1634                      l_objfundsum_rec.plan_curr_earned_amt := NVL(l_objfundsum_rec.plan_curr_earned_amt, 0)
1635                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1636                      l_objfundsum_rec.univ_curr_earned_amt := NVL(l_objfundsum_rec.univ_curr_earned_amt, 0)
1637                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1638 
1639                      l_objfundsum_rec.paid_amt := NVL(l_objfundsum_rec.paid_amt, 0) + NVL(l_utilization_rec.amount, 0);
1640                      l_objfundsum_rec.plan_curr_paid_amt := NVL(l_objfundsum_rec.plan_curr_paid_amt, 0)
1641                                                                   + NVL(l_utilization_rec.plan_curr_amount, 0);
1642                      l_objfundsum_rec.univ_curr_paid_amt := NVL(l_objfundsum_rec.univ_curr_paid_amt, 0)
1643                                                                   + NVL(l_utilization_rec.univ_curr_amount, 0);
1644                      -- end R12 changes
1645                   END IF;  */
1646             END IF; -- end of fund_type.
1647 
1648             UPDATE ozf_funds_all_b
1649             SET original_budget =  l_original_budget,
1650                 utilized_amt = l_utilized_amt,
1651                 earned_amt = l_earned_amt,
1652                 paid_amt = l_paid_amt,
1653                 object_version_number = l_obj_num + 1
1654                 ,rollup_original_budget = l_rollup_orig_amt
1655                 ,rollup_utilized_amt = l_rollup_utilized_amt
1656                 ,rollup_earned_amt = l_rollup_earned_amt
1657                 ,rollup_paid_amt = l_rollup_paid_amt
1658                 -- yzhao: 10/14/2003 Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
1659                 ,committed_amt = l_committed_amt
1660                 ,rollup_committed_amt = l_rollup_committed_amt
1661                 ,recal_committed = l_recal_committed
1662                 ,rollup_recal_committed = l_rollup_recal_committed
1663             WHERE fund_id =  l_utilization_rec.fund_id
1664             AND object_version_number = l_obj_num;
1665 
1666             IF l_parent_fund_id is NOT NULL THEN
1667                FOR fund IN c_parent(l_parent_fund_id)
1668                LOOP
1669                   UPDATE ozf_funds_all_b
1670                   SET object_version_number = fund.object_version_number + 1
1671                    ,rollup_original_budget = NVL(fund.rollup_original_budget,0) + NVL(l_new_orig_amt,0)
1672                    ,rollup_earned_amt = NVL(fund.rollup_earned_amt,0) + NVL(l_new_earned_amt,0)
1673                    ,rollup_paid_amt = NVL(fund.rollup_paid_amt,0) + NVL(l_new_paid_amt,0)
1674                    -- yzhao: 10/14/2003 Fix TEVA bug - customer fully accrual budget committed amount is always 0 even when accrual happens
1675                    ,rollup_committed_amt = NVL(fund.rollup_committed_amt, 0) + NVL(l_new_committed_amt, 0)
1676                    ,rollup_recal_committed = NVL(fund.rollup_recal_committed, 0) + NVL(l_new_recal_committed, 0)
1677                    -- yzhao: 11.5.10
1678                    ,rollup_utilized_amt = NVL(fund.rollup_utilized_amt,0) + NVL(l_new_utilized_amt,0)
1679                   WHERE fund_id = fund.fund_id
1680                   AND object_version_number = fund.object_version_number;
1681                 END LOOP;
1682             END IF;
1683 
1684           -- rimehrot: for R12, create or update in ozf_object_fund_summary
1685             IF l_objfundsum_rec.objfundsum_id IS NULL THEN
1686                l_objfundsum_rec.fund_id := l_utilization_rec.fund_id;
1687                l_objfundsum_rec.fund_currency := l_utilization_rec.currency_code;
1688                l_objfundsum_rec.object_type := l_utilization_rec.component_type;
1689                l_objfundsum_rec.object_id := l_utilization_rec.component_id;
1690                ozf_objfundsum_pvt.create_objfundsum(
1691                        p_api_version                => 1.0,
1692                        p_init_msg_list              => Fnd_Api.G_FALSE,
1693                        p_validation_level           => Fnd_Api.G_VALID_LEVEL_NONE,
1694                        p_objfundsum_rec             => l_objfundsum_rec,
1695                        x_return_status              => l_return_status,
1696                        x_msg_count                  => x_msg_count,
1697                        x_msg_data                   => x_msg_data,
1698                        x_objfundsum_id              => l_objfundsum_id
1699                 );
1700                IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1701                   RAISE fnd_api.g_exc_unexpected_error;
1702                ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
1703                   RAISE fnd_api.g_exc_error;
1704                END IF;
1705             ELSE
1706                ozf_objfundsum_pvt.update_objfundsum(
1707                        p_api_version                => 1.0,
1708                        p_init_msg_list              => Fnd_Api.G_FALSE,
1709                        p_validation_level           => Fnd_Api.G_VALID_LEVEL_NONE,
1710                        p_objfundsum_rec             => l_objfundsum_rec,
1711                        x_return_status              => l_return_status,
1712                        x_msg_count                  => x_msg_count,
1713                        x_msg_data                   => x_msg_data
1714                 );
1715                IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1716                   RAISE fnd_api.g_exc_unexpected_error;
1717                ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
1718                   RAISE fnd_api.g_exc_error;
1719                END IF;
1720             END IF;
1721             -- rimehrot: end changes for R12
1722 
1723           /* R12 yzhao: bug 4669269 - obsolete ozf_mc_transactions
1724           -- update ozf_mc_transaction_all table.
1725           UPDATE ozf_mc_transactions_all
1726             SET amount_column1 =l_mc_col_1,
1727                 amount_column6 =l_mc_col_6,   -- yzhao: 10/14/2003
1728                 amount_column7 =l_mc_col_7,
1729                 amount_column8 =l_mc_col_8,
1730                 amount_column9 =l_mc_col_9,   -- yzhao: 11.5.10 for utilized_amt
1731                 object_version_number = l_mc_obj_num + 1
1732             WHERE mc_record_id = l_mc_record_id
1733             AND object_version_number = l_mc_obj_num;
1734            */
1735          END IF; -- end if utilization type
1736 
1737         /* yzhao: 03/19/2003 post to GL when order is shipped. move to function post_accrual_to_gl */
1738 
1739         IF g_debug_flag = 'Y' THEN
1740          ozf_utility_pvt.write_conc_log(   l_full_name
1741                                      || ': end' || l_event_id);
1742         END IF;
1743 
1744         fnd_msg_pub.count_and_get (
1745             p_count=> x_msg_count,
1746             p_data=> x_msg_data,
1747             p_encoded=> fnd_api.g_false
1748          );
1749 
1750    EXCEPTION
1751       WHEN fnd_api.g_exc_error THEN
1752          ROLLBACK TO create_utilized_rec;
1753          x_return_status            := fnd_api.g_ret_sts_error;
1754          fnd_msg_pub.count_and_get (
1755             p_count=> x_msg_count,
1756             p_data=> x_msg_data,
1757             p_encoded=> fnd_api.g_false
1758          );
1759 
1760       WHEN fnd_api.g_exc_unexpected_error THEN
1761          ROLLBACK TO create_utilized_rec;
1762          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1763          fnd_msg_pub.count_and_get (
1764             p_count=> x_msg_count,
1765             p_data=> x_msg_data,
1766             p_encoded=> fnd_api.g_false
1767          );
1768 
1769       WHEN OTHERS THEN
1770          ROLLBACK TO create_utilized_rec;
1771          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1772          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1773             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1774          END IF;
1775          fnd_msg_pub.count_and_get (
1776             p_count=> x_msg_count,
1777             p_data=> x_msg_data,
1778             p_encoded=> fnd_api.g_false
1779          );
1780 
1781 
1782    END create_utilized_rec;
1783 
1784 ----------------------------------------------------------------------------------
1785 -- Procedure Name
1786 --  create_utilization
1787 -- created by mpande 02/08/2002
1788 -- Purpose
1789 --   This procedure will create utiliation records for the order accruals
1790 -----------------------------------------------------------------------------------
1791    PROCEDURE create_fund_utilization (
1792       p_act_util_rec      IN       ozf_fund_utilized_pvt.utilization_rec_type,
1793       p_act_budgets_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type,
1794       x_utilization_id    OUT NOCOPY      NUMBER,
1795       x_return_status     OUT NOCOPY      VARCHAR2,
1796       x_msg_count         OUT NOCOPY      NUMBER,
1797       x_msg_data          OUT NOCOPY      VARCHAR2
1798    ) IS
1799       l_api_version           NUMBER                                  := 1.0;
1800       l_api_name              VARCHAR2 (60)                           := 'create_fund_utilization';
1801       l_act_budget_id         NUMBER;
1802       l_act_budgets_rec       ozf_actbudgets_pvt.act_budgets_rec_type := p_act_budgets_rec;
1803       l_act_util_rec          ozf_fund_utilized_pvt.utilization_rec_type    := p_act_util_rec;
1804       l_activity_id           NUMBER;
1805       l_obj_ver_num           NUMBER;
1806       l_old_approved_amount   NUMBER;
1807       l_old_parent_src_amt    NUMBER;
1808       l_ledger_id             NUMBER;
1809       l_ledger_name           VARCHAR2(30);
1810       l_utilization_id        NUMBER;
1811 
1812       /* -- 6/3/2002 mpande changed as per PM specifications --
1813         We should accrue to the bill to org but not o the sold to org
1814       CURSOR c_cust_number (p_header_id IN NUMBER) IS
1815          SELECT sold_to_org_id
1816            FROM oe_order_headers_all
1817           WHERE header_id = p_header_id;
1818          */
1819       CURSOR c_cust_number (p_header_id IN NUMBER) IS
1820          SELECT cust.cust_account_id, header.invoice_to_org_id, header.ship_to_org_id
1821            FROM hz_cust_acct_sites_all acct_site,
1822                 hz_cust_site_uses_all site_use,
1823                 hz_cust_accounts  cust,
1824                 oe_order_headers_all header
1825           WHERE header.header_id = p_header_id
1826               AND acct_site.cust_acct_site_id = site_use.cust_acct_site_id
1827             AND acct_site.cust_account_id = cust.cust_account_id
1828             AND site_use.site_use_id = header.invoice_to_org_id ;
1829 
1830       -- Cursor to get the org_id for order
1831       CURSOR c_org_id (p_order_header_id IN NUMBER)IS
1832          SELECT org_id FROM oe_order_headers_all
1833          WHERE header_id = p_order_header_id;
1834 
1835    BEGIN
1836       SAVEPOINT create_fund_utilization_acr;
1837       x_return_status            := fnd_api.g_ret_sts_success;
1838       IF g_debug_flag = 'Y' THEN
1839          ozf_utility_pvt.write_conc_log ('    D:  Enter create_fund_utilization() ');
1840       END IF;
1841       l_act_util_rec.product_level_type := 'PRODUCT';
1842       IF l_act_util_rec.billto_cust_account_id IS NULL THEN
1843           --  customer id
1844           OPEN c_cust_number (p_act_util_rec.object_id);
1845           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;
1846           CLOSE c_cust_number;
1847       END IF;
1848 
1849       l_act_budgets_rec.justification := fnd_message.get_string ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK');
1850       l_act_budgets_rec.transfer_type := 'UTILIZED';
1851       l_act_budgets_rec.request_date := SYSDATE;
1852       l_act_budgets_rec.status_code := 'APPROVED';
1853       l_act_budgets_rec.user_status_id :=
1854             ozf_utility_pvt.get_default_user_status (
1855                'OZF_BUDGETSOURCE_STATUS',
1856                l_act_budgets_rec.status_code
1857             );
1858 
1859       ozf_utility_pvt.write_conc_log ('  l_act_budgets_rec.user_status_id '||l_act_budgets_rec.user_status_id);
1860       IF l_act_util_rec.org_id IS NULL THEN
1861           OPEN c_org_id( l_act_util_rec.object_id) ;
1862           FETCH c_org_id INTO l_act_util_rec.org_id;
1863           CLOSE c_org_id ;
1864       END IF;
1865 
1866       ozf_utility_pvt.write_conc_log ('  l_act_budgets_rec.org_id '||l_act_util_rec.org_id);
1867 
1868       --get the order's ledger id
1869       mo_utils.Get_Ledger_Info (p_operating_unit => l_act_util_rec.org_id
1870                                ,p_ledger_id      => l_ledger_id
1871                                ,p_ledger_name    => l_ledger_name);
1872 
1873       ozf_utility_pvt.write_conc_log (' l_ledger_id '||l_ledger_id);
1874       ozf_utility_pvt.write_conc_log (' l_ledger_name '|| l_ledger_name);
1875 
1876       create_actbudgets_rec (
1877         x_return_status       =>x_return_status
1878         ,x_msg_count          =>x_msg_count
1879         ,x_msg_data           =>x_msg_data
1880         ,x_act_budget_id      =>l_activity_id
1881         ,p_act_budgets_rec    =>l_act_budgets_rec
1882         ,p_ledger_id          => l_ledger_id        -- yzhao: added for R12
1883         ,p_org_id             =>l_act_util_rec.org_id -- nirprasa added to get conversion type for bug 7030415
1884       );
1885 
1886       IF x_return_status <> fnd_api.g_ret_sts_success THEN
1887          ozf_utility_pvt.write_conc_log (': create Act Budgets Failed '||x_return_status);
1888          IF x_return_status = fnd_api.g_ret_sts_error THEN
1889             RAISE fnd_api.g_exc_error;
1890          ELSIF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
1891             RAISE fnd_api.g_exc_unexpected_error;
1892          END IF;
1893       END IF;
1894 
1895       l_act_util_rec.ams_activity_budget_id := l_activity_id;
1896       create_utilized_rec (
1897         x_return_status      =>x_return_status
1898         ,x_msg_count           =>x_msg_count
1899         ,x_msg_data           =>x_msg_data
1900         ,x_utilization_id     =>l_utilization_id
1901         ,p_utilization_rec    =>l_act_util_rec
1902       );
1903 
1904       x_utilization_id := l_utilization_id;
1905 
1906       IF x_return_status <>fnd_api.g_ret_sts_success THEN
1907          ozf_utility_pvt.write_conc_log (': create utilization Failed '||x_return_status);
1908          IF x_return_status = fnd_api.g_ret_sts_error THEN
1909             RAISE fnd_api.g_exc_error;
1910          ELSIF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
1911             RAISE fnd_api.g_exc_unexpected_error;
1912          END IF;
1913       END IF;
1914 
1915       fnd_msg_pub.count_and_get (
1916          p_count=> x_msg_count,
1917          p_data=>x_msg_data,
1918          p_encoded=> fnd_api.g_false
1919       );
1920    EXCEPTION
1921       WHEN fnd_api.g_exc_error THEN
1922          ROLLBACK TO create_fund_utilization_acr;
1923          x_return_status            := fnd_api.g_ret_sts_error;
1924          fnd_msg_pub.count_and_get (
1925             p_count=> x_msg_count
1926            ,p_data=> x_msg_data
1927            ,p_encoded=> fnd_api.g_false
1928          );
1929       WHEN fnd_api.g_exc_unexpected_error THEN
1930          ROLLBACK TO create_fund_utilization_acr;
1931          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1932          fnd_msg_pub.count_and_get (
1933             p_count=> x_msg_count
1934            ,p_data=> x_msg_data
1935            ,p_encoded=> fnd_api.g_false
1936          );
1937       WHEN OTHERS THEN
1938          ROLLBACK TO create_fund_utilization_acr;
1939          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1940 
1941          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1942             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1943          END IF;
1944 
1945          fnd_msg_pub.count_and_get (
1946             p_count=> x_msg_count
1947            ,p_data=> x_msg_data
1948            ,p_encoded=> fnd_api.g_false
1949          );
1950    END create_fund_utilization;
1951 
1952 /*----------------------------------------------------------------------------
1953 -- Procedure Name
1954 --   post_accrual_to_budget
1955 -- Purpose
1956 --   This procedure will post accrual to budget proportionally, and create utilization records
1957 --   extracted from adjust_accrual so it can be reused
1958 --
1959 -- Parameters:
1960 --
1961 -- History
1962 --  created      yzhao     03/21/03
1963 ------------------------------------------------------------------------------*/
1964    PROCEDURE post_accrual_to_budget (
1965       p_adj_amt_tbl         IN  ozf_adjusted_amt_tbl_type,
1966       x_return_status       OUT NOCOPY      VARCHAR2,
1967       x_msg_count           OUT NOCOPY      NUMBER,
1968       x_msg_data            OUT NOCOPY      VARCHAR2
1969    ) IS
1970       l_return_status           VARCHAR2(1);
1971       l_offer_name              VARCHAR2(240);
1972       l_adj_amount              NUMBER;
1973       l_remaining_amount        NUMBER;
1974       l_rate                    NUMBER;
1975       l_converted_adj_amount    NUMBER;
1976       l_act_util_rec            ozf_actbudgets_pvt.act_util_rec_type;
1977       l_act_budgets_rec         ozf_actbudgets_pvt.act_budgets_rec_type;
1978       l_util_rec                ozf_fund_utilized_pvt.utilization_rec_type;
1979       l_fund_amt_tbl            ozf_fund_amt_tbl_type;
1980       l_cust_account_id         NUMBER;
1981       l_adjustment_date         DATE;
1982       l_bill_to_site_use_id     NUMBER;
1983       l_ship_to_site_use_id     NUMBER;
1984       l_utilization_id          NUMBER;
1985 
1986       l_order_org_id            NUMBER;
1987       l_exchange_rate_type      VARCHAR2(30) := FND_API.G_MISS_CHAR ;
1988 
1989        -- Added by rimehrot for R12
1990       CURSOR c_get_price_adj_dtl (p_price_adjustment_id IN NUMBER) IS
1991          SELECT creation_date
1992            FROM oe_price_adjustments adj
1993            WHERE adj.price_Adjustment_id = p_price_adjustment_id;
1994 
1995       CURSOR c_cust_number (p_header_id IN NUMBER) IS
1996          SELECT cust.cust_account_id, header.invoice_to_org_id, header.ship_to_org_id
1997            FROM hz_cust_acct_sites_all acct_site,
1998                 hz_cust_site_uses_all site_use,
1999                 hz_cust_accounts  cust,
2000                 oe_order_headers_all header
2001           WHERE header.header_id = p_header_id
2002               AND acct_site.cust_acct_site_id = site_use.cust_acct_site_id
2003             AND acct_site.cust_account_id = cust.cust_account_id
2004             AND site_use.site_use_id = header.invoice_to_org_id ;
2005 
2006       --Added for bug 7030415, get order's org_id
2007       CURSOR c_order_org_id (p_line_id IN NUMBER) IS
2008          SELECT header.org_id
2009          FROM oe_order_lines_all line, oe_order_headers_all header
2010          WHERE line_id = p_line_id
2011          AND line.header_id = header.header_id;
2012 
2013       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
2014          SELECT beneficiary_account_id,
2015                autopay_party_attr,autopay_party_id
2016            FROM ozf_offers
2017           WHERE qp_list_header_id = p_offer_id;
2018 
2019       --Added for bug 7030415, get conversion type
2020       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
2021          SELECT exchange_rate_type
2022          FROM   ozf_sys_parameters_all
2023          WHERE  org_id = p_org_id;
2024 
2025      --Added c_site_org_id for bug 6278466
2026       CURSOR c_site_org_id (p_site_use_id IN NUMBER) IS
2027          SELECT org_id
2028            FROM hz_cust_site_uses_all
2029           WHERE site_use_id = p_site_use_id;
2030 
2031       l_offer_type  c_offer_type%ROWTYPE;
2032 
2033 
2034    BEGIN
2035      x_return_status            := fnd_api.g_ret_sts_success;
2036 
2037      IF g_debug_flag = 'Y' THEN
2038         ozf_utility_pvt.write_conc_log('    D: Enter post_accrual_to_budget   p_adj_amt_tbl count=' || p_adj_amt_tbl.count);
2039      END IF;
2040 
2041      FOR i IN p_adj_amt_tbl.FIRST .. p_adj_amt_tbl.LAST
2042      LOOP
2043 
2044         IF g_debug_flag = 'Y' THEN
2045            ozf_utility_pvt.write_conc_log('D: Enter post_accrual_to_budget   price_adj_id=' || p_adj_amt_tbl(i).price_adjustment_id ||
2046                            ' amount=' || p_adj_amt_tbl(i).earned_amount);
2047         END IF;
2048 
2049         l_fund_amt_tbl.DELETE;
2050 
2051         OPEN c_cust_number(p_adj_amt_tbl(i).order_header_id);
2052         FETCH c_cust_number INTO l_cust_account_id, l_bill_to_site_use_id, l_ship_to_site_use_id;
2053         CLOSE c_cust_number;
2054 
2055         ozf_accrual_engine.calculate_accrual_amount (
2056           x_return_status  => l_return_status,
2057           p_src_id         => p_adj_amt_tbl(i).qp_list_header_id,
2058           p_earned_amt     => p_adj_amt_tbl(i).earned_amount,
2059           p_cust_account_type => 'BILL_TO',
2060           p_cust_account_id => l_cust_account_id,
2061           p_product_item_id => p_adj_amt_tbl(i).product_id,
2062           x_fund_amt_tbl   => l_fund_amt_tbl
2063         );
2064 
2065         IF g_debug_flag = 'Y' THEN
2066            ozf_utility_pvt.write_conc_log ('    D: post_adjust_to_budget(): Calculate Accrual Amount returns' || l_return_status);
2067         END IF;
2068 
2069         IF l_return_status <> fnd_api.g_ret_sts_success THEN
2070            IF l_return_status = fnd_api.g_ret_sts_error THEN
2071               RAISE fnd_api.g_exc_error;
2072            ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
2073               RAISE fnd_api.g_exc_unexpected_error;
2074            END IF;
2075         END IF;
2076 
2077         --- if this is not funded by a parent campaign or any budget the error OUT NOCOPY saying no budgte found
2078         IF l_fund_amt_tbl.COUNT = 0 THEN
2079            IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
2080               fnd_message.set_name ('OZF', 'OZF_FUND_NO_BUDGET_FOUND');
2081               fnd_message.set_token ('OFFER_ID', p_adj_amt_tbl(i).qp_list_header_id);
2082               fnd_msg_pub.ADD;
2083            END IF;
2084            IF g_debug_flag = 'Y' THEN
2085               ozf_utility_pvt.write_conc_log('    D: post_adjust_to_budget()  calculation for posting to budget failed. No posting to budget. RETURN');
2086            END IF;
2087            -- yzhao: 03/26/2003 should continue or error out?
2088            --RETURN;
2089            --kdass 24-MAR-2007 bug 5900966 - if no budget is attached to the offer, then move to process next record
2090            GOTO l_endofadjamtloop;
2091         END IF;
2092 
2093         l_adj_amount := 0; -- in offer currency
2094         l_remaining_amount  := p_adj_amt_tbl(i).earned_amount; -- in offer currency
2095 
2096         IF g_debug_flag = 'Y' THEN
2097            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);
2098         END IF;
2099 
2100         -- added by rimehrot for R12
2101         OPEN c_get_price_adj_dtl (p_adj_amt_tbl(i).price_adjustment_id);
2102         FETCH c_get_price_adj_dtl INTO l_adjustment_date;
2103         CLOSE c_get_price_adj_dtl;
2104 
2105         FOR j IN l_fund_amt_tbl.FIRST .. l_fund_amt_tbl.LAST
2106         LOOP
2107            l_act_budgets_rec :=NULL;
2108            l_util_rec :=NULL;
2109            IF l_remaining_amount >= l_fund_amt_tbl (j).earned_amount THEN
2110              l_adj_amount := l_fund_amt_tbl (j).earned_amount; -- this is in offer and order currency
2111            ELSE
2112              l_adj_amount := l_remaining_amount;
2113            END IF;
2114            l_remaining_amount := l_remaining_amount - l_adj_amount;
2115 
2116            IF p_adj_amt_tbl(i).offer_currency = l_fund_amt_tbl (j).budget_currency THEN
2117               l_act_budgets_rec.parent_src_apprvd_amt :=l_adj_amount;
2118            ELSE
2119               IF g_debug_flag = 'Y' THEN
2120                  ozf_utility_pvt.write_conc_log ('    D: post_adjust_to_budget() In not equal currency');
2121               END IF;
2122 
2123               -- Added for bug 7030415, get the order's org_id to get the exchange rate.
2124 
2125               /*Adjustment amount is converted from offer curr to budgets curr to populate
2126               parent_src_apprvd_amt column in izf_act_budgets table and amount column
2127               of ozf_funds_utilized_all_b table*/
2128 
2129                  OPEN c_order_org_id(p_adj_amt_tbl(i).order_line_id);
2130                  FETCH c_order_org_id INTO l_order_org_id;
2131                  CLOSE c_order_org_id;
2132 
2133                  OPEN c_offer_type(p_adj_amt_tbl(i).qp_list_header_id);
2134                  FETCH c_offer_type INTO l_offer_type;
2135                  CLOSE c_offer_type;
2136 
2137                  IF l_util_rec.cust_account_id IS NULL THEN
2138                    IF l_offer_type.beneficiary_account_id IS NOT NULL THEN
2139                     IF l_offer_type.autopay_party_attr <> 'CUSTOMER' AND l_offer_type.autopay_party_attr IS NOT NULL THEN
2140 
2141                       OPEN c_site_org_id (l_offer_type.autopay_party_id);
2142                       FETCH c_site_org_id INTO l_order_org_id;
2143                       CLOSE c_site_org_id;
2144 
2145                         END IF;
2146                     END IF;
2147                 END IF;
2148 
2149                  OPEN c_get_conversion_type(l_order_org_id);
2150                  FETCH c_get_conversion_type INTO l_exchange_rate_type;
2151                  CLOSE c_get_conversion_type;
2152 
2153                 IF g_debug_flag = 'Y' THEN
2154                   ozf_utility_pvt.write_conc_log('**************************START****************************');
2155                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' From Amount l_adj_amount: '||l_adj_amount );
2156                   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 );
2157                   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);
2158                   ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' l_exchange_rate_type: '|| l_exchange_rate_type);
2159                 END IF;
2160 
2161               ozf_utility_pvt.convert_currency (
2162                x_return_status => l_return_status,
2163                p_from_currency => p_adj_amt_tbl(i).offer_currency,
2164                p_to_currency   => l_fund_amt_tbl (j).budget_currency,
2165                p_conv_type     => l_exchange_rate_type, -- nirprasa added for bug 7030415
2166                p_from_amount   => l_adj_amount,
2167                x_to_amount     => l_converted_adj_amount,
2168                x_rate          => l_rate
2169               );
2170 
2171                IF g_debug_flag = 'Y' THEN
2172                 ozf_utility_pvt.write_conc_log('post_accrual_to_budget' ||' Converted Amount l_converted_adj_amount: '|| l_converted_adj_amount);
2173                 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');
2174                 ozf_utility_pvt.write_conc_log('***************************END******************************');
2175               END IF;
2176 
2177               IF l_return_status <> fnd_api.g_ret_sts_success THEN
2178                  IF g_debug_flag = 'Y' THEN
2179                     ozf_utility_pvt.write_conc_log ('   D: post_adjust_to_budget() convert currency failed. No posting to budget. Return');
2180                  END IF;
2181                  RAISE fnd_api.g_exc_unexpected_error;
2182               END IF;
2183               l_act_budgets_rec.parent_src_apprvd_amt :=l_converted_adj_amount;
2184            END IF;
2185 
2186            IF g_debug_flag = 'Y' THEN
2187               ozf_utility_pvt.write_conc_log (   '    D: post_adjust_to_budget() Adj amount coverted ' || l_converted_adj_amount
2188               || ' l_adj amount '     || l_adj_amount        );
2189            END IF;
2190 
2191            l_act_budgets_rec.budget_source_type := 'OFFR';
2192            l_act_budgets_rec.budget_source_id := p_adj_amt_tbl(i).qp_list_header_id;
2193            l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
2194            l_act_budgets_rec.act_budget_used_by_id := p_adj_amt_tbl(i).qp_list_header_id;
2195            l_act_budgets_rec.parent_src_curr := l_fund_amt_tbl (j).budget_currency;
2196            l_act_budgets_rec.parent_source_id := l_fund_amt_tbl (j).ofr_src_id;
2197            l_act_budgets_rec.request_amount :=l_adj_amount;
2198            l_act_budgets_rec.request_currency := p_adj_amt_tbl(i).offer_currency;
2199            l_act_budgets_rec.approved_amount := l_act_budgets_rec.request_amount;
2200            l_act_budgets_rec.approved_in_currency := p_adj_amt_tbl(i).offer_currency;
2201            -- added by rimehrot for R12
2202            l_util_rec.bill_to_site_use_id := l_bill_to_site_use_id;
2203            l_util_rec.ship_to_site_use_id := l_ship_to_site_use_id;
2204            l_util_rec.billto_cust_account_id := l_cust_account_id;
2205            l_util_rec.adjustment_date := l_adjustment_date;
2206            l_util_rec.object_type := 'ORDER';
2207            l_util_rec.object_id   := p_adj_amt_tbl(i).order_header_id;
2208            l_util_rec.price_adjustment_id := p_adj_amt_tbl(i).price_adjustment_id;
2209            l_util_rec.amount := l_act_budgets_rec.parent_src_apprvd_amt;
2210            l_util_rec.plan_curr_amount := l_act_budgets_rec.request_amount;
2211            l_util_rec.component_type := 'OFFR';
2212            l_util_rec.component_id := p_adj_amt_tbl(i).qp_list_header_id ;
2213            l_util_rec.currency_code := l_fund_amt_tbl (j).budget_currency;
2214            l_util_rec.fund_id := l_fund_amt_tbl(j).ofr_src_id;
2215            l_util_rec.product_id := p_adj_amt_tbl(i).product_id ;
2216            l_util_rec.volume_offer_tiers_id := NULL;
2217            l_util_rec.gl_posted_flag := G_GL_FLAG_NO;  -- 'N'
2218            l_util_rec.billto_cust_account_id := l_cust_account_id;
2219            l_util_rec.order_line_id := p_adj_amt_tbl(i).order_line_id;
2220 
2221            create_fund_utilization (
2222                 p_act_util_rec     => l_util_rec,
2223                 p_act_budgets_rec  => l_act_budgets_rec,
2224                 x_utilization_id   => l_utilization_id,
2225                 x_return_status    => l_return_status,
2226                 x_msg_count        => x_msg_count,
2227                 x_msg_data         => x_msg_data
2228               );
2229            IF l_return_status <> fnd_api.g_ret_sts_success THEN
2230               IF g_debug_flag = 'Y' THEN
2231                  ozf_utility_pvt.write_conc_log ('D: post_adjust_to_budget() create_fund_utilization() returns error. Exception');
2232               END IF;
2233               RAISE fnd_api.g_exc_unexpected_error;
2234            END IF;
2235 
2236            <<l_endofearadjloop>>
2237 
2238            IF g_debug_flag = 'Y' THEN
2239               ozf_utility_pvt.write_conc_log ( '    D: post_adjust_to_budget()  loop iteration end l_remaining_amount ' || l_remaining_amount
2240                 || ' l_adj amount '|| l_adj_amount || ' fund_id '
2241                 || l_fund_amt_tbl (j).ofr_src_id        );
2242            END IF;
2243 
2244            EXIT WHEN l_remaining_amount = 0;
2245         END LOOP earned_adj_loop;
2246 
2247         <<l_endofadjamtloop>>
2248 
2249         IF g_debug_flag = 'Y' THEN
2250            ozf_utility_pvt.write_conc_log('D: Ends successfully post_accrual_to_budget   price_adj_id=' || p_adj_amt_tbl(i).price_adjustment_id
2251                   || ' amount=' || p_adj_amt_tbl(i).earned_amount);
2252         END IF;
2253 
2254      END LOOP; -- p_adj_amt_tbl
2255 
2256      IF g_debug_flag = 'Y' THEN
2257         ozf_utility_pvt.write_conc_log('D: Ends of post_accrual_to_budget');
2258      END IF;
2259 
2260      x_return_status   := fnd_api.g_ret_sts_success;
2261 
2262      fnd_msg_pub.count_and_get (
2263             p_count=> x_msg_count,
2264             p_data=> x_msg_data,
2265             p_encoded=> fnd_api.g_false
2266          );
2267 
2268    EXCEPTION
2269       WHEN OTHERS THEN
2270         x_return_status            := fnd_api.g_ret_sts_unexp_error;
2271         ozf_utility_pvt.write_conc_log (' /**************UNEXPECTED EXCEPTION in ozf_accrual_engine.post_accrual_to_budget');
2272         IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2273            fnd_msg_pub.add_exc_msg ('ozf_accrual_engine', 'post_accrual_to_budget');
2274         END IF;
2275         fnd_msg_pub.count_and_get (
2276             p_count=> x_msg_count,
2277             p_data=> x_msg_data,
2278             p_encoded=> fnd_api.g_false
2279          );
2280   END post_accrual_to_budget;
2281 
2282 ------------------------------------------------------------------------------
2283 -- Procedure Name
2284 --   Adjust_Accrual
2285 -- Purpose
2286 --   This procedure will calculate and update the accrual info.
2287 --
2288 --  created      pjindal     06/20/00
2289 --  updated      mpande      07/18/00
2290 --  updated      mpande      08/02/00 -- changed the fund_utlization creation calls
2291 --  updated      mpande      02/02/01 -- changed the fund_type checks , benifit  limit checks
2292 --  updated      mpande      12/28/2001  -- added line and header info also
2293 ------------------------------------------------------------------------------
2294    PROCEDURE adjust_accrual (
2295       p_api_version        IN       NUMBER,
2296       p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false,
2297       p_commit             IN       VARCHAR2 := fnd_api.g_false,
2298       p_validation_level   IN       NUMBER := fnd_api.g_valid_level_full,
2299       x_return_status      OUT NOCOPY      VARCHAR2,
2300       x_msg_count          OUT NOCOPY      NUMBER,
2301       x_msg_data           OUT NOCOPY      VARCHAR2,
2302       p_line_adj_tbl       IN       oe_order_pub.line_adj_tbl_type,
2303       p_old_line_adj_tbl   IN       oe_order_pub.line_adj_tbl_type,
2304       p_header_rec         IN       oe_order_pub.header_rec_type := NULL,
2305       p_exception_queue    IN       VARCHAR2 := fnd_api.g_false
2306 
2307    ) IS
2308       l_return_status           VARCHAR2 (10)                           := fnd_api.g_ret_sts_success;
2309       l_api_name       CONSTANT VARCHAR2 (30)                           := 'Adjust_Accrual';
2310       l_api_version    CONSTANT NUMBER                                  := 1.0;
2311       l_earned_amount           NUMBER;
2312       l_old_earned_amount       NUMBER;
2313       l_util_id                 NUMBER;
2314       l_adj_amount              NUMBER;
2315       l_line_quantity           NUMBER;
2316       l_old_adjusted_amount     NUMBER    := 0;
2317       l_cancelled_quantity      NUMBER;
2318       l_modifier_level_code     VARCHAR2 (30);
2319       l_new_adjustment_amount   NUMBER;
2320       l_line_category_code      VARCHAR2(30);
2321       l_range_break             NUMBER;
2322       l_operation               VARCHAR2(30);
2323       l_product_id              NUMBER;
2324       l_util_rec                ozf_fund_utilized_pvt.utilization_rec_type;
2325       l_act_budgets_rec         ozf_actbudgets_pvt.act_budgets_rec_type;
2326       l_gl_posted_flag          VARCHAR2 (1);
2327       l_utilization_id          NUMBER;
2328       l_gl_date                 DATE;
2329       l_object_version_number   NUMBER;
2330       l_plan_type               VARCHAR2(30);
2331       l_utilization_type        VARCHAR2(30);
2332       l_amount                  NUMBER;
2333       l_fund_id                 NUMBER;
2334       l_acctd_amount            NUMBER;
2335       l_order_curr              VARCHAR2(30);
2336       l_offer_curr              VARCHAR2(30);
2337       l_count                   NUMBER            := 0;
2338       l_adj_amt_tbl             ozf_adjusted_amt_tbl_type;
2339       l_plan_id                 NUMBER;
2340       l_plan_amount             NUMBER;
2341       l_rate                    NUMBER;
2342       l_conv_earned_amount      NUMBER;
2343       l_conv_adjustment_amount  NUMBER;
2344       l_util_exists             NUMBER;
2345       l_new_line_id             NUMBER;
2346 
2347       l_order_org_id            NUMBER;
2348       l_exchange_rate_type      VARCHAR2(30) := FND_API.G_MISS_CHAR;
2349 
2350       CURSOR c_line_info (p_line_id IN NUMBER) IS
2351          SELECT line.inventory_item_id,
2352                 line.ordered_quantity,
2353                 line.cancelled_quantity,
2354                 line.line_category_code,
2355                 header.transactional_curr_code,
2356                 header.org_id
2357          FROM oe_order_lines_all line, oe_order_headers_all header
2358          WHERE line_id = p_line_id
2359            AND line.header_id = header.header_id;
2360 
2361       CURSOR c_list_line_info (p_list_line_id IN NUMBER) IS
2362          SELECT estim_gl_value
2363          FROM qp_list_lines
2364          WHERE list_line_id = p_list_line_id;
2365 
2366       CURSOR c_old_adjustment_amount (p_price_adjustment_id IN NUMBER) IS
2367          SELECT SUM (plan_curr_amount)
2368          FROM ozf_funds_utilized_all_b
2369          WHERE price_adjustment_id = p_price_adjustment_id
2370          AND object_type = 'ORDER';
2371 
2372       CURSOR c_order_count (p_header_id IN NUMBER) IS
2373          SELECT SUM (ordered_quantity - NVL (cancelled_quantity, 0))
2374          FROM oe_order_lines_all
2375          WHERE header_id = p_header_id;
2376 
2377          -- Added adjusted_amount for bug fix 4173825
2378       CURSOR c_mod_level (p_price_ad_id IN NUMBER) IS
2379          SELECT modifier_level_code,range_break_quantity, adjusted_amount
2380          FROM oe_price_adjustments
2381          WHERE price_adjustment_id = p_price_ad_id;
2382 
2383       -- Added component_type,utilization_type for bug fix 5523042
2384       CURSOR c_old_adjustment_amt (p_price_adjustment_id IN NUMBER) IS
2385          SELECT  NVL (amount, 0) amount,
2386                   fund_id,
2387                   currency_code,
2388                   NVL (plan_curr_amount, 0) plan_curr_amount,
2389                   gl_posted_flag, product_id,component_type,utilization_type
2390          FROM ozf_funds_utilized_all_b
2391          WHERE price_adjustment_id = p_price_adjustment_id
2392          AND object_type = 'ORDER';
2393          --GROUP BY fund_id, currency_code, price_adjustment_id, gl_posted_flag, product_id ;
2394 
2395       CURSOR c_get_util_rec(p_utilization_id IN NUMBER) IS
2396        SELECT  object_version_number, plan_type, utilization_type, amount, fund_id, acctd_amount, plan_id, plan_curr_amount
2397        FROM   ozf_funds_utilized_all_b
2398        WHERE  utilization_id = p_utilization_id;
2399 
2400       CURSOR c_tm_offer (p_list_header_id IN NUMBER) IS
2401          SELECT nvl(transaction_currency_code,fund_request_curr_code) transaction_currency_code
2402          FROM ozf_offers
2403          WHERE qp_list_header_id = p_list_header_id;
2404 
2405       CURSOR c_get_util (p_list_header_id IN NUMBER, p_header_id IN NUMBER, p_line_id IN NUMBER) IS
2406          SELECT 1
2407          FROM ozf_funds_utilized_all_b
2408          WHERE plan_type = 'OFFR'
2409          AND plan_id = p_list_header_id
2410          AND object_type = 'ORDER'
2411          AND object_id = p_header_id
2412          AND order_line_id = p_line_id
2413          AND utilization_type = 'ADJUSTMENT'
2414          AND price_adjustment_id IS NULL;
2415 
2416       CURSOR c_split_line(p_line_id IN NUMBER) IS
2417         SELECT line_id
2418         FROM oe_order_lines_all
2419         WHERE split_from_line_id IS NOT NULL
2420         AND line_id = p_line_id
2421         AND split_by = 'SYSTEM';
2422 
2423       -- added for bug 7030415 get conversion type
2424       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
2425          SELECT exchange_rate_type
2426          FROM   ozf_sys_parameters_all
2427          WHERE  org_id = p_org_id;
2428 
2429       BEGIN
2430          SAVEPOINT adjust_accrual;
2431          -- Standard call to check for call compatibility.
2432          IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
2433             RAISE fnd_api.g_exc_unexpected_error;
2434          END IF;
2435          -- Initialize message list IF p_init_msg_list is set to TRUE.
2436          IF fnd_api.to_boolean (p_init_msg_list) THEN
2437             fnd_msg_pub.initialize;
2438          END IF;
2439          --  Initialize API return status to success
2440          x_return_status            := fnd_api.g_ret_sts_success;
2441 
2442          <<new_line_tbl_loop>>
2443 
2444          IF g_debug_flag = 'Y' THEN
2445             ozf_utility_pvt.write_conc_log ('  D: Inside New Line Table Loop');
2446          END IF;
2447 
2448          l_adj_amt_tbl.DELETE;
2449 
2450          FOR i IN NVL (p_line_adj_tbl.FIRST, 1) .. NVL (p_line_adj_tbl.LAST, 0)
2451          LOOP
2452             x_return_status            := fnd_api.g_ret_sts_success;
2453             SAVEPOINT line_adjustment;
2454 
2455             IF g_debug_flag = 'Y' THEN
2456               ozf_utility_pvt.write_conc_log ('    /++++++++ ADJUSTMENT DEBUG MESSAGE START +++++++++/'          );
2457               ozf_utility_pvt.write_conc_log ('    D: Begin Processing For Price Adjustment Id # '|| p_line_adj_tbl(i).price_adjustment_id          );
2458             END IF;
2459 
2460             IF  p_line_adj_tbl (i).list_line_type_code IN
2461                                               ('CIE', 'DIS', 'IUE', 'OID',  'PLL', 'PMR', 'TSN','PBH')
2462                 AND p_line_adj_tbl (i).applied_flag = 'Y'
2463            THEN
2464 
2465               OPEN c_tm_offer ( p_line_adj_tbl (i).list_header_id);
2466               FETCH c_tm_offer INTO l_offer_curr;
2467 
2468             -- check if it is a TM Offers
2469               IF c_tm_offer%NOTFOUND THEN
2470                  CLOSE c_tm_offer;
2471                  IF g_debug_flag = 'Y' THEN
2472                     ozf_utility_pvt.write_conc_log('D  not TM offer: offer id:  ' ||  p_line_adj_tbl(i).list_header_id);
2473                  END IF;
2474                  GOTO l_endoflineadjloop;
2475               ELSE
2476                  CLOSE c_tm_offer;
2477               END IF;
2478 
2479               l_line_quantity            := 0;
2480               l_old_adjusted_amount      := 0;
2481               l_cancelled_quantity       := 0;
2482               l_earned_amount            := 0;
2483 
2484               IF g_debug_flag = 'Y' THEN
2485                  ozf_utility_pvt.write_conc_log ('    D: Operation '|| p_line_adj_tbl (i).operation ||
2486                  ' Order header id  ' || p_line_adj_tbl (i).header_id || ' Line id  ' || p_line_adj_tbl (i).line_id  );
2487               END IF;
2488 
2489               OPEN c_line_info (p_line_adj_tbl (i).line_id);
2490               FETCH c_line_info INTO l_product_id,
2491                                      l_line_quantity,
2492                                      l_cancelled_quantity,
2493                                      l_line_category_code,
2494                                      l_order_curr,
2495                                      l_order_org_id;
2496               CLOSE c_line_info;
2497 
2498                --Added for bug 7030415
2499               OPEN c_get_conversion_type(l_order_org_id);
2500               FETCH c_get_conversion_type INTO l_exchange_rate_type;
2501               CLOSE c_get_conversion_type;
2502 
2503               IF p_exception_queue = fnd_api.g_true AND p_line_adj_tbl (i).operation = 'CREATE' THEN
2504                  l_operation := 'UPDATE' ;
2505               ELSE
2506                  l_operation := p_line_adj_tbl (i).operation;
2507               END IF;
2508 
2509               IF l_operation <> 'DELETE' THEN
2510                  OPEN c_mod_level (p_line_adj_tbl (i).price_adjustment_id);
2511                  FETCH c_mod_level INTO l_modifier_level_code,l_range_break, l_new_adjustment_amount;
2512                  CLOSE c_mod_level;
2513 
2514                  IF g_debug_flag = 'Y' THEN
2515                     ozf_utility_pvt.write_conc_log ('    D: Modifier level code '|| l_modifier_level_code);
2516                  END IF;
2517               END IF;
2518 
2519               IF g_debug_flag = 'Y' THEN
2520                  ozf_utility_pvt.write_conc_log (
2521                   '    D: Line quantity '|| l_line_quantity || ' Cancelled quantity ' || l_cancelled_quantity ||
2522                   '   line_adj_tbl.adjusted_amount=' || l_new_adjustment_amount
2523                  );
2524               END IF;
2525 
2526               IF l_modifier_level_code = 'ORDER' THEN
2527                   -- for the time being this is the workaround cause there is no way to find out how much adjustment for total
2528                   -- has happened due to this order level offer
2529                  l_cancelled_quantity       := 0;
2530                  OPEN c_order_count (p_line_adj_tbl (i).header_id);
2531                  FETCH c_order_count INTO l_line_quantity;
2532                  CLOSE c_order_count;
2533               END IF;
2534 
2535               --kdass 24-FEB-07 bug 5485334 - do not create utilization when offer gets applied on
2536               --order booked before offer start date on manual re-pricing order
2537               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);
2538               FETCH c_get_util INTO l_util_exists;
2539               CLOSE c_get_util;
2540 
2541               IF NVL(l_util_exists,0) = 1 THEN
2542                  IF g_debug_flag = 'Y' THEN
2543                     ozf_utility_pvt.write_conc_log('Manual re-pricing of order created before offer start date. No utilization.');
2544                  END IF;
2545                  GOTO l_endoflineadjloop;
2546               END IF;
2547 
2548               IF l_operation = 'CREATE' THEN
2549                  IF g_debug_flag = 'Y' THEN
2550                     ozf_utility_pvt.write_conc_log ('operation create');
2551                  END IF;
2552 
2553                  l_earned_amount := (-(NVL(l_new_adjustment_amount, 0))) * l_line_quantity;
2554 
2555                  IF g_debug_flag = 'Y' THEN
2556                     ozf_utility_pvt.write_conc_log('    D: adjust_accrual()_ create  earned amount = ' || l_earned_amount);
2557                  END IF;
2558 
2559                  IF l_line_category_code = 'RETURN' THEN
2560                     IF g_debug_flag = 'Y' THEN
2561                        ozf_utility_pvt.write_conc_log ( '   LINE IS RETURN  ');
2562                     END IF;
2563                     l_earned_amount := -l_earned_amount;
2564                  END IF;
2565 
2566                   -- if it is a TSN then get the gl value of the upgrade
2567                  IF p_line_adj_tbl (i).list_line_type_code = 'TSN' THEN
2568                     OPEN c_list_line_info (p_line_adj_tbl (i).list_line_id);
2569                     FETCH c_list_line_info INTO l_earned_amount;
2570                     CLOSE c_list_line_info;
2571                      -- Multiply with the quantity ordered
2572                      -- 5/2/2002 mpande modified ordered qty is the line quantity
2573                     l_earned_amount            :=    l_earned_amount * (l_line_quantity);
2574                  END IF;
2575 
2576                  --kdass 31-MAR-2006 bug 5101720 - convert from order currency to offer currency
2577                   IF l_offer_curr <> l_order_curr THEN
2578 
2579                      ozf_utility_pvt.write_conc_log('l_order_curr: ' || l_order_curr);
2580                      ozf_utility_pvt.write_conc_log('l_offer_curr: ' || l_offer_curr);
2581                      ozf_utility_pvt.write_conc_log('l_earned_amount: ' || l_earned_amount);
2582 
2583                      IF g_debug_flag = 'Y' THEN
2584                        ozf_utility_pvt.write_conc_log('l_order_org_id: ' || l_order_org_id);
2585                        ozf_utility_pvt.write_conc_log('**************************START****************************');
2586                        ozf_utility_pvt.write_conc_log(l_api_name||' From Amount l_earned_amount: '||l_earned_amount );
2587                        ozf_utility_pvt.write_conc_log(l_api_name||' From Curr l_order_curr: '||l_order_curr );
2588                        ozf_utility_pvt.write_conc_log(l_api_name||' l_exchange_rate_type: '|| l_exchange_rate_type);
2589                       END IF;
2590 
2591                      ozf_utility_pvt.convert_currency (x_return_status => x_return_status
2592                                                       ,p_from_currency => l_order_curr
2593                                                       ,p_to_currency   => l_offer_curr
2594                                                       ,p_conv_type     => l_exchange_rate_type -- Added for bug 7030415
2595                                                       ,p_from_amount   => l_earned_amount
2596                                                       ,x_to_amount     => l_conv_earned_amount
2597                                                       ,x_rate          => l_rate
2598                                                       );
2599 
2600                      IF g_debug_flag = 'Y' THEN
2601                         ozf_utility_pvt.write_conc_log(l_api_name||' To Curr l_offer_curr: '|| l_offer_curr );
2602                         ozf_utility_pvt.write_conc_log(l_api_name||' Converted Amount l_conv_earned_amount: '|| l_conv_earned_amount);
2603                         ozf_utility_pvt.write_conc_log('Earned amount is converted from order curr to offer curr');
2604                         ozf_utility_pvt.write_conc_log('***************************END******************************');
2605                         ozf_utility_pvt.write_conc_log('x_return_status: ' || x_return_status);
2606                      END IF;
2607 
2608                      IF x_return_status <> fnd_api.g_ret_sts_success THEN
2609                         GOTO l_endoflineadjloop;
2610                      END IF;
2611 
2612                      l_earned_amount := l_conv_earned_amount;
2613 
2614                      IF g_debug_flag = 'Y' THEN
2615                        ozf_utility_pvt.write_conc_log ('earned amt after currency conversion: ' || l_earned_amount);
2616                      END IF;
2617                   END IF;
2618 
2619               ELSIF l_operation = 'UPDATE' THEN
2620                  IF g_debug_flag = 'Y' THEN
2621                     ozf_utility_pvt.write_conc_log ('operation UPDATE');
2622                  END IF;
2623                   -- if the old and the new is the same we donot need to update it \
2624                  OPEN c_old_adjustment_amount (p_line_adj_tbl (i).price_adjustment_id);
2625                  FETCH c_old_adjustment_amount INTO l_old_adjusted_amount; -- in order curr
2626                  CLOSE c_old_adjustment_amount;
2627 
2628                  IF g_debug_flag = 'Y' THEN
2629                     ozf_utility_pvt.write_conc_log (
2630                      '    D: Old adjsutment amount '
2631                      || l_old_adjusted_amount
2632                      || '  Old price adjustment id '
2633                      || p_line_adj_tbl (i).price_adjustment_id
2634                      );
2635                  END IF;
2636                   -- if all the money coming in has been adjusted then set it to 0
2637                   --5/2/2002 the ordered quantity is the actual ordered quantity and not the difference
2638                  IF l_line_category_code = 'RETURN' THEN
2639                     IF g_debug_flag = 'Y' THEN
2640                        ozf_utility_pvt.write_conc_log ( '   LINE IS RETURN  ');
2641                     END IF;
2642                     l_line_quantity := -l_line_quantity; -- fred should be cancelled qutity.
2643                  END IF;
2644 
2645                  l_new_adjustment_amount    :=   (l_line_quantity )
2646                                              * (-(NVL (l_new_adjustment_amount, 0)));
2647 
2648                  IF g_debug_flag = 'Y' THEN
2649                     ozf_utility_pvt.write_conc_log('    D: adjust_accrual() l_new_adjustment_amount=' || l_new_adjustment_amount );
2650                  END IF;
2651 
2652                   --kdass 31-MAR-2006 bug 5101720 - convert from order currency to offer currency and the do rounding
2653                   IF l_offer_curr <> l_order_curr THEN
2654 
2655                      ozf_utility_pvt.write_conc_log('l_order_curr: ' || l_order_curr);
2656                      ozf_utility_pvt.write_conc_log('l_offer_curr: ' || l_offer_curr);
2657                      ozf_utility_pvt.write_conc_log('l_new_adjustment_amount: ' || l_new_adjustment_amount);
2658 
2659                      ozf_utility_pvt.convert_currency (x_return_status => x_return_status
2660                                                       ,p_from_currency => l_order_curr
2661                                                       ,p_to_currency   => l_offer_curr
2662                                                       ,p_conv_type     => l_exchange_rate_type -- Added for bug 7030415
2663                                                       ,p_from_amount   => l_new_adjustment_amount
2664                                                       ,x_to_amount     => l_conv_adjustment_amount
2665                                                       ,x_rate          => l_rate
2666                                                       );
2667 
2668                      ozf_utility_pvt.write_conc_log('x_return_status: ' || x_return_status);
2669 
2670                      IF x_return_status <> fnd_api.g_ret_sts_success THEN
2671                         GOTO l_endoflineadjloop;
2672                      END IF;
2673 
2674                      l_new_adjustment_amount := l_conv_adjustment_amount;
2675 
2676                      IF g_debug_flag = 'Y' THEN
2677                         ozf_utility_pvt.write_conc_log ('new adjusted amt after currency conversion: ' || l_new_adjustment_amount);
2678                      END IF;
2679                   END IF;
2680 
2681                  l_earned_amount            :=  l_new_adjustment_amount - NVL(l_old_adjusted_amount,0);
2682 
2683                  IF g_debug_flag = 'Y' THEN
2684                     ozf_utility_pvt.write_conc_log ('    D: Update earned amount '|| l_earned_amount);
2685                  END IF;
2686 
2687                 -- Changes by rimehrot (12/8/2004) for bug 3697213
2688                -- When order is re-priced and offer is removed from the order, a message with operation
2689                -- 'DELETE' is sent and the original accrual should be reverted in this case.
2690               ELSIF l_operation = 'DELETE' AND p_line_adj_tbl (i).price_adjustment_id IS NOT NULL THEN
2691                  IF g_debug_flag = 'Y' THEN
2692                    ozf_utility_pvt.write_conc_log ('operation DELETE');
2693                  END IF;
2694 
2695                  FOR old_adjustment_rec IN
2696                    c_old_adjustment_amt (p_line_adj_tbl (i).price_adjustment_id)
2697                  LOOP
2698                     l_adj_amount := -old_adjustment_rec.amount;
2699                     IF old_adjustment_rec.amount = 0 THEN
2700                        GOTO l_endofloop;
2701                     END IF;
2702 
2703                     l_util_rec :=NULL;
2704                     l_act_budgets_rec :=NULL;
2705                     l_util_rec.object_type := 'ORDER';
2706                     l_util_rec.object_id   := p_line_adj_tbl (i).header_id;
2707                     l_util_rec.product_id := old_adjustment_rec.product_id;
2708                     l_util_rec.price_adjustment_id := p_line_adj_tbl (i).price_adjustment_id;
2709                     l_act_budgets_rec.budget_source_type := 'OFFR';
2710                     l_act_budgets_rec.budget_source_id := p_line_adj_tbl (i).list_header_id;
2711                     l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
2712                     l_act_budgets_rec.act_budget_used_by_id := p_line_adj_tbl (i).list_header_id;
2713                     l_act_budgets_rec.parent_src_apprvd_amt := l_adj_amount;
2714                     l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
2715                     l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
2716                     l_act_budgets_rec.request_amount := -old_adjustment_rec.plan_curr_amount;
2717                     l_act_budgets_rec.request_currency := l_order_curr;
2718                     l_util_rec.amount := l_adj_amount ;
2719                     l_util_rec.plan_curr_amount :=  l_act_budgets_rec.request_amount;
2720                     l_util_rec.component_id := p_line_adj_tbl (i).list_header_id;
2721                     l_util_rec.currency_code :=old_adjustment_rec.currency_code;
2722                     l_util_rec.fund_id :=old_adjustment_rec.fund_id;
2723                     -- kpatro 11/09/2006 fix for bug 5523042
2724                     l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
2725                     l_util_rec.component_type := old_adjustment_rec.component_type;
2726 
2727 
2728                   -- yzhao: 06/23/2004 if old record needs to post, set this gl flag to N, otherwise, no posting
2729                     IF old_adjustment_rec.gl_posted_flag IN (G_GL_FLAG_NULL, G_GL_FLAG_NOLIAB) THEN
2730                        l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;  -- 'N';
2731                     ELSE
2732                        l_util_rec.gl_posted_flag := G_GL_FLAG_NO;  -- 'N';
2733                     END IF;
2734                   -- rimehrot: initially put the gl_posted_flag as N. If post_accrual_to_gl call reqd later,
2735                   -- will get changed accordingly depending on the value obtained after posting.
2736 
2737                     create_fund_utilization (
2738                        p_act_util_rec=> l_util_rec,
2739                      p_act_budgets_rec=> l_act_budgets_rec,
2740                      x_utilization_id => l_utilization_id,
2741                      x_return_status=> l_return_status,
2742                      x_msg_count=> x_msg_count,
2743                      x_msg_data=> x_msg_data
2744                      );
2745 
2746                     IF g_debug_flag = 'Y' THEN
2747                        ozf_utility_pvt.write_conc_log (
2748                         'create utlization from cancelled order returns '|| l_return_status
2749                        );
2750                     END IF;
2751 
2752                     IF l_return_status <> fnd_api.g_ret_sts_success THEN
2753                        GOTO l_endoflineadjloop;
2754                     END IF;
2755 
2756                   -- If gl_posted_flag of original accrual has been posted, call post_accrual_to_gl
2757                   -- to post new accrual
2758 
2759                     IF old_adjustment_rec.gl_posted_flag IN (G_GL_FLAG_YES, G_GL_FLAG_FAIL) THEN
2760                     -- get details of utilization created above.
2761                     -- fred could be removed. direct to use from above cursor.
2762                        OPEN c_get_util_rec (l_utilization_id);
2763                        FETCH c_get_util_rec INTO l_object_version_number, l_plan_type, l_utilization_type, l_amount,
2764                           l_fund_id, l_acctd_amount, l_plan_id, l_plan_amount;
2765                        CLOSE c_get_util_rec;
2766 
2767                        post_accrual_to_gl( p_util_utilization_id            => l_utilization_id
2768                                      , p_util_object_version_number      => l_object_version_number
2769                                      , p_util_amount                     => l_amount
2770                                      , p_util_plan_type                  => l_plan_type
2771                                      , p_util_plan_id                    => l_plan_id
2772                                      , p_util_plan_amount                => l_plan_amount
2773                                      , p_util_utilization_type           => l_utilization_type
2774                                      , p_util_fund_id                    => l_fund_id
2775                                      , p_util_acctd_amount               => l_acctd_amount
2776                                      , x_gl_posted_flag                  => l_gl_posted_flag
2777                                      , x_return_status                   => l_return_status
2778                                      , x_msg_count                       => x_msg_count
2779                                      , x_msg_data                        => x_msg_data
2780                                      );
2781 
2782                    -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
2783                        IF g_debug_flag = 'Y' THEN
2784                           ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() processing price adjustment id' || p_line_adj_tbl (i).line_id
2785                           || '  post_accrual_to_gl(util_id=' || l_utilization_id ||
2786                            ' gl_posted_flag' || l_gl_posted_flag || ') returns ' || l_return_status);
2787                        END IF;
2788                     END IF; -- end of gl_posted_flag in (Y, F)
2789 
2790                     <<l_endofloop>>
2791                     NULL;
2792                  END LOOP old_adjustment_rec;
2793                END IF; -- end if for mode
2794 
2795                --6373391
2796 
2797                ozf_utility_pvt.write_conc_log('NP line_id '||p_line_adj_tbl (i).line_id);
2798 
2799                OPEN c_split_line(p_line_adj_tbl (i).line_id);
2800                FETCH c_split_line INTO l_new_line_id;
2801                CLOSE c_split_line;
2802 
2803                ozf_utility_pvt.write_conc_log('NP  l_new_line_id '||l_new_line_id);
2804 
2805 
2806                -- OM sometimes is not sending create message for new split line . So handle it in TM.
2807                -- and create accrual so that we get a rec in utilization table for split line
2808 
2809                IF  NVL(l_earned_amount,0) = 0 AND p_line_adj_tbl (i).operation <> 'CREATE'
2810                AND NVL(l_new_line_id,0) = 0 THEN
2811                   IF g_debug_flag = 'Y' THEN
2812                      ozf_utility_pvt.write_conc_log('    D: adjust_accrual()  earned amount = 0. No adjustment');
2813                   END IF;
2814                   GOTO l_endoflineadjloop;
2815                END IF;
2816 
2817 
2818                ozf_utility_pvt.write_conc_log('NP LG P1 creating adjustment for '||l_new_line_id);
2819 
2820                IF g_debug_flag = 'Y' THEN
2821                   ozf_utility_pvt.write_conc_log('    D: adjust_accrual()  earned amount = ' || l_earned_amount);
2822                END IF;
2823 
2824                l_count := l_count + 1;
2825                l_adj_amt_tbl (l_count).order_header_id := p_line_adj_tbl (i).header_id;
2826                l_adj_amt_tbl (l_count).order_line_id := p_line_adj_tbl (i).line_id;
2827                l_adj_amt_tbl (l_count).price_adjustment_id := p_line_adj_tbl (i).price_adjustment_id;
2828                l_adj_amt_tbl (l_count).qp_list_header_id:= p_line_adj_tbl (i).list_header_id;
2829                l_adj_amt_tbl (l_count).product_id := l_product_id;
2830                --l_adj_amt_tbl (l_count).earned_amount := ozf_utility_pvt.currround (l_earned_amount, l_order_curr);
2831                l_adj_amt_tbl (l_count).earned_amount := l_earned_amount;
2832                l_adj_amt_tbl (l_count).offer_currency:= l_offer_curr;
2833             END IF;
2834             <<l_endoflineadjloop>>
2835 
2836             IF x_return_status <> fnd_api.g_ret_sts_success THEN
2837                IF g_debug_flag = 'Y' THEN
2838                   ozf_utility_pvt.write_conc_log (
2839                     '   /****** Adjustment Failure *******/ Offer Id: "'|| p_line_adj_tbl(i).list_header_id ||'"' || 'Price Adjustment Id'||p_line_adj_tbl (i).price_adjustment_id);
2840                END IF;
2841                   -- Initialize the Message list for Next Processing
2842                ROLLBACK TO line_adjustment;
2843                x_return_status := fnd_api.g_ret_sts_error ;
2844                EXIT;
2845             ELSE
2846                IF g_debug_flag = 'Y' THEN
2847                   ozf_utility_pvt.write_conc_log(
2848                     '   /****** Adjustment Success *******/ Offer Id: "'|| p_line_adj_tbl(i).list_header_id ||
2849                     '"' || ' Price Adjustment Id "'||p_line_adj_tbl (i).price_Adjustment_id ||'"' );
2850                END IF;
2851             END IF;
2852 
2853          END LOOP new_line_tbl_loop;
2854 
2855          IF l_adj_amt_tbl.count > 0 THEN
2856             post_accrual_to_budget (
2857                    p_adj_amt_tbl         => l_adj_amt_tbl
2858                  , x_return_status       => l_return_status
2859                  , x_msg_count           => x_msg_count
2860                  , x_msg_data            => x_msg_data
2861             );
2862          END IF;
2863 
2864          IF g_debug_flag = 'Y' THEN
2865             ozf_utility_pvt.write_conc_log('    D: post_accrual_to_budget returns ' || l_return_status);
2866          END IF;
2867          x_return_status  := l_return_status;
2868          fnd_msg_pub.count_and_get (
2869             p_count=> x_msg_count,
2870             p_data=> x_msg_data,
2871             p_encoded=> fnd_api.g_false
2872          );
2873 
2874    EXCEPTION
2875       WHEN OTHERS THEN
2876         --ROLLBACK TO adjust_accrual;
2877         x_return_status            := fnd_api.g_ret_sts_unexp_error;
2878         ozf_utility_pvt.write_conc_log(' /**************UNEXPECTED EXCEPTION in adjust_accrual *************/');
2879         IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2880            fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
2881         END IF;
2882         fnd_msg_pub.count_and_get (
2883             p_count=> x_msg_count,
2884             p_data=> x_msg_data,
2885             p_encoded=> fnd_api.g_false
2886          );
2887    END adjust_accrual;
2888 
2889 ------------------------------------------------------------------------------
2890 -- Procedure Name
2891 --   adjust_changed_order
2892 -- Purpose
2893 --   This procedure will calculate and update the accrual info for cancelled order
2894 --     and post to gl for shipped order.
2895 --
2896 --  created      mpande     02/15/2002
2897 --  modified     yzhao      03/19/2003   added posting to GL for shipped order lines
2898 ------------------------------------------------------------------------------
2899    PROCEDURE adjust_changed_order (
2900       p_api_version        IN       NUMBER,
2901       p_init_msg_list      IN       VARCHAR2 := fnd_api.g_false,
2902       p_commit             IN       VARCHAR2 := fnd_api.g_false,
2903       p_validation_level   IN       NUMBER := fnd_api.g_valid_level_full,
2904       x_return_status      OUT NOCOPY      VARCHAR2,
2905       x_msg_count          OUT NOCOPY      NUMBER,
2906       x_msg_data           OUT NOCOPY      VARCHAR2,
2907       p_header_rec         IN       oe_order_pub.header_rec_type,
2908       p_old_header_rec     IN       oe_order_pub.header_rec_type,
2909       p_line_tbl           IN       oe_order_pub.line_tbl_type,
2910       p_old_line_tbl       IN       oe_order_pub.line_tbl_type
2911    ) IS
2912       l_return_status           VARCHAR2 (1)                          ;
2913       l_api_name       CONSTANT VARCHAR2 (30)                           := 'Adjust_Changed_order';
2914       l_api_version    CONSTANT NUMBER                                  := 1.0;
2915       --  local variables
2916       l_qp_list_hdr_id          NUMBER;
2917       l_earned_amount           NUMBER;
2918       l_old_earned_amount       NUMBER;
2919       l_header_id               NUMBER; -- order or invoice id
2920       l_line_id                 NUMBER; -- order or invoice id
2921       l_util_rec                ozf_fund_utilized_pvt.utilization_rec_type;
2922       l_empty_util_rec          ozf_fund_utilized_pvt.utilization_rec_type;
2923       l_util_id                 NUMBER;
2924       l_util_curr               VARCHAR2 (30);
2925       l_adj_amount              NUMBER;
2926       l_converted_adj_amount    NUMBER;
2927       l_order_status            VARCHAR2 (30);
2928       l_order_booked_flag       VARCHAR2 (1);
2929       l_line_quantity           NUMBER;
2930       l_old_adjusted_amount     NUMBER                                  := 0;
2931       l_order_curr              VARCHAR2 (150);
2932       l_cancelled_quantity      NUMBER;
2933       l_modifier_level_code     VARCHAR2 (30);
2934       l_line_status             VARCHAR2 (30);
2935       l_new_adjustment_amount   NUMBER;
2936       l_act_budgets_rec         ozf_actbudgets_pvt.act_budgets_rec_type;
2937       l_empty_act_budgets_rec   ozf_actbudgets_pvt.act_budgets_rec_type;
2938       l_order_number            NUMBER;
2939       l_gl_posted_flag          VARCHAR2 (1);
2940       l_orig_adj_amount         NUMBER;
2941       l_rate                    NUMBER;
2942       l_total                   NUMBER;
2943       l_gl_date                 DATE;
2944       l_new_line_id             NUMBER;
2945       l_new_adj_id              NUMBER;
2946       l_sales_transaction_rec   OZF_SALES_TRANSACTIONS_PVT.SALES_TRANSACTION_REC_TYPE;
2947       l_sales_transaction_id    NUMBER;
2948       l_org_id                  NUMBER;
2949       l_sales_trans             NUMBER;
2950       l_utilization_id          NUMBER;
2951 
2952       l_utilIdTbl               utilIdTbl;
2953       l_objVerTbl               objVerTbl;
2954       l_amountTbl               amountTbl;
2955       l_planTypeTbl             planTypeTbl;
2956       l_planIdTbl               planIdTbl;
2957       l_planAmtTbl              planAmtTbl;
2958       l_utilTypeTbl             utilTypeTbl;
2959       l_fundIdTbl               fundIdTbl;
2960       l_acctAmtTbl              acctAmtTbl;
2961       l_orgIdTbl                orgIdTbl;
2962 
2963       CURSOR party_id_csr(p_cust_account_id NUMBER) IS
2964          SELECT party_id
2965          FROM hz_cust_accounts
2966          WHERE cust_account_id = p_cust_account_id;
2967 
2968       CURSOR party_site_id_csr(p_account_site_id NUMBER) IS
2969          SELECT a.party_site_id
2970          FROM hz_cust_acct_sites_all a,
2971               hz_cust_site_uses_all b
2972          WHERE b.site_use_id = p_account_site_id
2973          AND   b.cust_acct_site_id = a.cust_acct_site_id;
2974 
2975       CURSOR sales_transation_csr(p_line_id NUMBER) IS
2976          SELECT 1 FROM DUAL WHERE EXISTS
2977          ( SELECT 1
2978            FROM ozf_sales_transactions_all trx
2979            WHERE trx.line_id = p_line_id
2980            AND source_code = 'OM');
2981 
2982       CURSOR c_order_info (p_header_id IN NUMBER) IS
2983          SELECT flow_status_code,
2984                 booked_flag,
2985                 transactional_curr_code,
2986                 order_number,
2987                 org_id
2988          FROM oe_order_headers_all
2989          WHERE header_id = p_header_id;
2990 
2991       CURSOR c_all_price_adjustments (p_line_id IN NUMBER) IS
2992          SELECT price_adjustment_id,
2993                 list_header_id,
2994                 adjusted_amount,          -- yzhao: 03/21/2003 added following 2 for shipped order
2995                 header_id
2996          FROM oe_price_adjustments
2997          WHERE line_id = p_line_id;
2998 
2999       -- used for cancelled order and partial ship.
3000       CURSOR c_old_adjustment_amount (p_price_adjustment_id IN NUMBER) IS
3001          SELECT    plan_curr_amount, amount,
3002                    fund_id,currency_code,
3003                    gl_posted_flag,plan_id,
3004                    utilization_type,price_adjustment_id,
3005                    adjustment_type,orig_utilization_id,
3006                    exchange_rate_type --nirprasa
3007          FROM ozf_funds_utilized_all_b
3008          WHERE price_adjustment_id = p_price_adjustment_id
3009          AND object_type = 'ORDER'
3010          AND NVL(gl_posted_flag,'N') <> 'Y';
3011 
3012       -- yzhao: 03/21/2003 get old adjustment amount per price_adjustment_id, copy from adjust_accrual
3013       CURSOR c_old_adjustment_total_amount (p_price_adjustment_id IN NUMBER) IS
3014          SELECT SUM (plan_curr_amount)  -- change to plan_curr_amount from acct_amount by feliu
3015          FROM ozf_funds_utilized_all_b
3016          WHERE price_adjustment_id = p_price_adjustment_id
3017          AND object_type = 'ORDER'
3018          AND utilization_type NOT IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT'); -- remove adjustment amount on 08/03/04 by feliu
3019 
3020      -- yzhao: 03/21/2003 get shipped/invoiced order's accraul record, post to GL
3021      -- changed for bug 6140826
3022      CURSOR c_get_accrual_rec(p_line_id IN NUMBER) IS
3023         SELECT utilization_id, object_version_number, plan_type, utilization_type, amount
3024              , fund_id, acctd_amount, plan_curr_amount, plan_id,org_id
3025         FROM   ozf_funds_utilized_all_b
3026         WHERE  price_adjustment_id IN (SELECT price_adjustment_id
3027                                       FROM   oe_price_adjustments
3028                                       WHERE  line_id = p_line_id)
3029         AND    gl_posted_flag = G_GL_FLAG_NO  -- 'N'
3030         AND object_type = 'ORDER'
3031        -- 05/11/2004  kdass  fixed bug 3609771 - added UTILIZED to query
3032         AND    utilization_type in ('ACCRUAL', 'LEAD_ACCRUAL','SALES_ACCRUAL')
3033         UNION ALL -- added for bug 5485334 kpatro
3034         select utilization_id, object_version_number, plan_type, utilization_type, amount
3035              , fund_id, acctd_amount, plan_curr_amount, plan_id,org_id
3036               from  ozf_funds_utilized_all_b
3037         where object_type = 'ORDER'
3038         and order_line_id = p_line_id
3039         AND  gl_posted_flag = G_GL_FLAG_NO
3040         AND utilization_type IN ('ADJUSTMENT','LEAD_ADJUSTMENT')
3041            AND (price_adjustment_id IS NULL or (price_adjustment_id =-1 and orig_utilization_id<>-1)); --added for bug 6021635 nirprasa
3042 
3043 
3044      CURSOR c_actual_shipment_date(p_line_id IN NUMBER) IS
3045         SELECT actual_shipment_date
3046         FROM oe_order_lines_all
3047         WHERE line_id = p_line_id;
3048 
3049      CURSOR c_invoice_date(p_line_id IN NUMBER, p_order_number IN VARCHAR2) IS
3050         SELECT  cust.trx_date     -- transaction(invoice) date
3051         FROM ra_customer_trx_all cust
3052            , ra_customer_trx_lines_all cust_lines
3053         WHERE cust.customer_trx_id = cust_lines.customer_trx_id
3054         AND cust_lines.sales_order = p_order_number -- added condition for partial index for bug fix 3917556
3055         AND cust_lines.interface_line_attribute6 = TO_CHAR(p_line_id);
3056 
3057      -- add by feliu on 08/03/04, get split line id to use in create postivie adjustment.
3058      CURSOR c_split_line(p_line_id IN NUMBER) IS
3059         SELECT line_id
3060         FROM oe_order_lines_all
3061         WHERE split_from_line_id = p_line_id
3062         AND   split_by = 'SYSTEM';
3063 
3064      -- add by feliu on 08/03/04, get price_adjustment_id to use in create postivie adjustment.
3065      CURSOR c_new_adj_line(p_line_id IN NUMBER, p_header_id IN NUMBER) IS
3066         SELECT price_adjustment_id
3067         FROM  oe_price_adjustments
3068         WHERE line_id = p_line_id
3069         AND   list_header_id = p_header_id;
3070      -- add by feliu on 08/03/04, get max utilization id to use in create  adjustment.
3071      CURSOR c_max_utilized_id(p_price_adj_id IN NUMBER) IS
3072         SELECT max(utilization_id)
3073         FROM ozf_funds_utilized_all_b
3074         WHERE price_adjustment_id = p_price_adj_id
3075         AND object_type = 'ORDER';
3076 
3077       CURSOR c_orig_order_info (p_line_id IN NUMBER) IS
3078          SELECT NVL(shipped_quantity,ordered_quantity)
3079          FROM oe_order_lines_all
3080          WHERE line_id =p_line_id;
3081 
3082       CURSOR c_orig_adjustment_amount (p_order_line_id IN NUMBER) IS
3083          SELECT    plan_curr_amount, amount,
3084                    fund_id,currency_code,
3085                    gl_posted_flag,plan_id,
3086                    utilization_type,price_adjustment_id,
3087                    adjustment_type,orig_utilization_id
3088         FROM ozf_funds_utilized_all_b
3089         WHERE order_line_id = p_order_line_id
3090         AND adjustment_type_id IN(-4,-5);
3091 
3092       --kdass bug 5953774
3093       CURSOR c_offer_currency (p_list_header_id IN NUMBER) IS
3094              SELECT nvl(transaction_currency_code, fund_request_curr_code) offer_currency
3095            FROM ozf_offers
3096            WHERE qp_list_header_id = p_list_header_id;
3097 
3098 
3099 
3100         --added for bug
3101                 CURSOR c_old_adj_total_amount (p_order_line_id IN NUMBER) IS
3102          SELECT SUM (plan_curr_amount)  -- change to plan_curr_amount from acct_amount by feliu
3103          FROM ozf_funds_utilized_all_b
3104          WHERE price_adjustment_id = -1
3105          and order_line_id=p_order_line_id
3106          AND object_type = 'ORDER'
3107          AND utilization_type  IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT'); --
3108 
3109            CURSOR c_old_adjustment_details (p_order_line_id IN NUMBER) IS
3110           SELECT    plan_curr_amount, amount,
3111                    fund_id,currency_code,
3112                    gl_posted_flag,plan_id,
3113                    utilization_type,price_adjustment_id,
3114                    adjustment_type,orig_utilization_id
3115          FROM ozf_funds_utilized_all_b
3116          WHERE price_adjustment_id = -1
3117           and order_line_id=p_order_line_id
3118          AND object_type = 'ORDER'
3119          AND utilization_id=(
3120         SELECT max(utilization_id)
3121         FROM ozf_funds_utilized_all_b
3122         WHERE price_adjustment_id = -1
3123             and order_line_id=p_order_line_id
3124         AND object_type = 'ORDER');
3125 
3126 
3127          CURSOR  c_split_order_line_info(p_order_line_id IN NUMBER)  IS
3128         SELECT DECODE(line.line_category_code,'ORDER',line.ordered_quantity,
3129                                                                             'RETURN', -line.ordered_quantity) ordered_quantity,
3130              DECODE(line.line_category_code,'ORDER',NVL(line.shipped_quantity,0),
3131                                                                             'RETURN', line.invoiced_quantity,
3132                                                                             line.ordered_quantity) shipped_quantity
3133 
3134         FROM oe_order_lines_all line, oe_order_headers_all header
3135         WHERE line.line_id = p_order_line_id
3136         AND line.header_id = header.header_id;
3137 
3138 
3139          CURSOR c_all_fund_utilizations (p_line_id IN NUMBER) IS
3140         SELECT price_adjustment_id , plan_id
3141          FROM ozf_funds_utilized_all_b
3142          WHERE order_line_id = p_line_id;
3143 
3144          CURSOR c_offer_type (p_offer_id IN NUMBER) IS
3145          SELECT offer_type
3146          FROM   ozf_offers
3147          WHERE  qp_list_header_id = p_offer_id;
3148 
3149           CURSOR c_discount_header(p_discount_line_id IN NUMBER) IS
3150          SELECT discount_type,volume_type
3151           FROM ozf_offer_discount_lines
3152           WHERE offer_discount_line_id = p_discount_line_id
3153           AND tier_type = 'PBH';
3154 
3155      CURSOR c_get_group(p_order_line_id IN NUMBER,p_list_header_id IN NUMBER) IS
3156        SELECT group_no,pbh_line_id,include_volume_flag
3157         FROM ozf_order_group_prod
3158         WHERE order_line_id = p_order_line_id
3159         AND qp_list_header_id = p_list_header_id;
3160 
3161      CURSOR c_market_option(p_list_header_id IN NUMBER, p_group_id IN NUMBER) IS
3162        SELECT opt.retroactive_flag
3163         FROM ozf_offr_market_options opt
3164         WHERE opt.GROUP_NUMBER= p_group_id
3165         AND opt.qp_list_header_id = p_list_header_id;
3166 
3167            CURSOR c_current_discount(p_volume IN NUMBER, p_parent_discount_id IN NUMBER) IS
3168          SELECT discount
3169         FROM ozf_offer_discount_lines
3170         WHERE p_volume > volume_from
3171              AND p_volume <= volume_to
3172          AND parent_discount_line_id = p_parent_discount_id;
3173 
3174           CURSOR  c_get_tier_limits (p_parent_discount_id IN NUMBER) IS
3175        SELECT MIN(volume_from),MAX(volume_to)
3176        FROM ozf_offer_discount_lines
3177        WHERE parent_discount_line_id = p_parent_discount_id;
3178 
3179      CURSOR  c_get_max_tier (p_max_volume_to IN NUMBER,p_parent_discount_id IN NUMBER)    IS
3180         SELECT  discount
3181         FROM ozf_offer_discount_lines
3182         WHERE volume_to =p_max_volume_to
3183         AND parent_discount_line_id = p_parent_discount_id;
3184 
3185    CURSOR c_discount(p_order_line_id  IN NUMBER) IS
3186        SELECT SUM(adjusted_amount_per_pqty)
3187        FROM oe_price_adjustments
3188        WHERE line_id = p_order_line_id
3189        AND accrual_flag = 'N'
3190        AND applied_flag = 'Y'
3191       -- AND list_line_type_code IN ('DIS', 'SUR', 'PBH', 'FREIGHT_CHARGE');
3192        AND list_line_type_code IN ('DIS', 'SUR', 'PBH');
3193         --
3194 
3195       l_shipped_qty   NUMBER;
3196       l_offer_curr    VARCHAR2(150);
3197       l_offer_amount  NUMBER;
3198 
3199       l_ordered_qty   NUMBER;
3200       l_offer_type    VARCHAR2(240);
3201 
3202        l_group_id                NUMBER;
3203       l_pbh_line_id             NUMBER;
3204       l_included_vol_flag       VARCHAR2(1);
3205       l_retroactive             VARCHAR2(1) ;
3206       l_discount_type           VARCHAR2(30);
3207       l_volume_type             VARCHAR2(30);
3208 
3209       l_msg_count               NUMBER;
3210       l_msg_data                VARCHAR2 (2000)        := NULL;
3211       l_source_code             VARCHAR2(30);
3212       l_volume                  NUMBER;
3213       l_new_discount            NUMBER;
3214       l_min_tier                NUMBER;
3215       l_max_tier                NUMBER;
3216       l_utilization_amount      NUMBER;
3217       l_unit_selling_price      NUMBER;
3218       l_unit_discount           NUMBER;
3219 
3220 
3221    BEGIN
3222       SAVEPOINT adjust_changed_order;
3223       -- Standard call to check for call compatibility.
3224       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
3225          RAISE fnd_api.g_exc_unexpected_error;
3226       END IF;
3227       -- Initialize message list IF p_init_msg_list is set to TRUE.
3228       IF fnd_api.to_boolean (p_init_msg_list) THEN
3229          fnd_msg_pub.initialize;
3230       END IF;
3231       --  Initialize API return status to success
3232       x_return_status            := fnd_api.g_ret_sts_success;
3233       <<new_line_tbl_loop>>
3234 
3235       IF g_debug_flag = 'Y' THEN
3236          ozf_utility_pvt.write_conc_log (
3237             ' /*************************** DEBUG MESSAGE START for adjust_changed_line *************************/');
3238       END IF;
3239 
3240       FOR i IN NVL (p_line_tbl.FIRST, 1) .. NVL (p_line_tbl.LAST, 0)
3241       LOOP
3242          savepoint line_adjustment;
3243          IF g_debug_flag = 'Y' THEN
3244             ozf_utility_pvt.write_conc_log (
3245             '    D: Begin Processing For Order Line '|| p_line_tbl(i).line_id || ' cancelled_flag=' || p_line_tbl (i).cancelled_flag
3246                );
3247          END IF;
3248 
3249          IF g_debug_flag = 'Y' THEN
3250             ozf_utility_pvt.write_conc_log ('    D: AQ info for order header_id=' || p_line_tbl(i).header_id
3251                           -- || ' p_line_tbl(i).operation=' || p_line_tbl(i).operation
3252                            || ' p_line_tbl(i).flow_status_code=' || p_line_tbl(i).flow_status_code
3253                            || ' p_line_tbl(i).line_id=' || p_line_tbl(i).line_id
3254                            || ' p_line_tbl(i).ordered_quantity=' || p_line_tbl(i).ordered_quantity
3255                            || ' p_line_tbl(i).shipped_quantity=' || p_line_tbl(i).shipped_quantity
3256                            || ' p_line_tbl(i).invoiced_quantity=' || p_line_tbl(i).invoiced_quantity
3257                            || ' p_line_tbl(i).invoice_interface_status_code=' || p_line_tbl(i).invoice_interface_status_code
3258                            || ' p_line_tbl(i).line_category_code=' || p_line_tbl(i).line_category_code );
3259             ozf_utility_pvt.write_conc_log ('    D: AQ info for old order header_id=' || p_line_tbl(i).header_id
3260                           -- || ' p_line_tbl(i).operation=' || p_line_tbl(i).operation
3261                            || ' p_old_line_tbl(i).flow_status_code=' || p_old_line_tbl(i).flow_status_code
3262                            || ' p_old_line_tbl(i).line_id=' || p_old_line_tbl(i).line_id
3263                            || ' p_old_line_tbl(i).ordered_quantity=' || p_old_line_tbl(i).ordered_quantity
3264                            || ' p_old_line_tbl(i).shipped_quantity=' || p_old_line_tbl(i).shipped_quantity
3265                            || ' p_old_line_tbl(i).invoiced_quantity=' || p_old_line_tbl(i).invoiced_quantity
3266                            || ' p_old_line_tbl(i).invoice_interface_status_code=' || p_old_line_tbl(i).invoice_interface_status_code
3267                            || ' p_old_line_tbl(i).line_category_code=' || p_old_line_tbl(i).line_category_code );
3268          END IF;
3269 
3270          IF p_line_tbl (i).cancelled_flag = 'Y' THEN
3271 
3272             FOR price_adjustment_rec IN c_all_price_adjustments (p_line_tbl (i).line_id)
3273             LOOP
3274 
3275                FOR old_adjustment_rec IN
3276                    c_old_adjustment_amount (price_adjustment_rec.price_adjustment_id)
3277                LOOP
3278 
3279                   l_adj_amount := -old_adjustment_rec.amount;
3280 
3281                   IF old_adjustment_rec.amount = 0 THEN
3282                      GOTO l_endofloop;
3283                   END IF;
3284 
3285                   l_util_rec := l_empty_util_rec;
3286                   l_act_budgets_rec :=l_empty_act_budgets_rec;
3287                   l_act_budgets_rec.budget_source_type := 'OFFR';
3288                   l_act_budgets_rec.budget_source_id := old_adjustment_rec.plan_id;
3289                   l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3290                   l_act_budgets_rec.act_budget_used_by_id := old_adjustment_rec.plan_id;
3291                   l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
3292                   l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
3293                   l_util_rec.object_type := 'ORDER';
3294                   l_util_rec.object_id   := p_line_tbl (i).header_id;
3295                   l_util_rec.product_id := p_line_tbl(i).inventory_item_id;
3296                   l_util_rec.price_adjustment_id := old_adjustment_rec.price_adjustment_id;
3297                   l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
3298                   l_util_rec.component_id :=old_adjustment_rec.plan_id;
3299                   l_util_rec.component_type := 'OFFR';
3300                   l_util_rec.currency_code :=old_adjustment_rec.currency_code;
3301                   l_util_rec.fund_id :=old_adjustment_rec.fund_id;
3302                   l_util_rec.order_line_id := p_line_tbl (i).line_id;
3303                   l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;
3304                   l_act_budgets_rec.parent_src_apprvd_amt := l_adj_amount;
3305                   l_act_budgets_rec.request_amount :=-old_adjustment_rec.plan_curr_amount;
3306                   l_util_rec.amount := l_adj_amount ;
3307                   l_util_rec.plan_curr_amount :=  l_act_budgets_rec.request_amount;
3308 
3309                   IF old_adjustment_rec.utilization_type  = 'ADJUSTMENT' THEN
3310                      l_util_rec.adjustment_type_id :=-4;
3311                      l_util_rec.adjustment_type := 'DECREASE_EARNED';
3312                      l_util_rec.orig_utilization_id := old_adjustment_rec.orig_utilization_id;
3313                   END IF;
3314 
3315                   create_fund_utilization (
3316                         p_act_util_rec=> l_util_rec,
3317                         p_act_budgets_rec=> l_act_budgets_rec,
3318                         x_utilization_id => l_utilization_id,
3319                         x_return_status=> l_return_status,
3320                         x_msg_count=> x_msg_count,
3321                         x_msg_data=> x_msg_data
3322                      );
3323 
3324                   IF g_debug_flag = 'Y' THEN
3325                      ozf_utility_pvt.write_conc_log (
3326                        '    D: create utlization from cancelled order returns '|| l_return_status);
3327                   END IF;
3328 
3329                   IF l_return_status <> fnd_api.g_ret_sts_success THEN
3330                      GOTO l_endoflineadjloop;
3331                   END IF;
3332                   --- quit when the total earned amount is adjusted
3333                   <<l_endofloop>>
3334                   NULL;
3335                END LOOP old_adjustment_rec;
3336             END LOOP; -- end loop for price adjustment rec
3337          END IF;   -- if for cancelled flag
3338 
3339 
3340          IF p_line_tbl (i).reference_line_id IS NOT NULL
3341             --AND p_line_tbl (i).flow_status_code = 'FULFILLED'
3342             AND p_line_tbl (i).line_category_code ='RETURN'
3343             AND p_line_tbl(i).invoiced_quantity IS NOT NULL THEN
3344 
3345             IF g_debug_flag = 'Y' THEN
3346                ozf_utility_pvt.write_conc_log('    D: adjusted_changed_order: RMA with reference: ' || p_line_tbl(i).reference_line_id);
3347             END IF;
3348 
3349             OPEN c_orig_order_info (p_line_tbl (i).reference_line_id);
3350             FETCH c_orig_order_info INTO l_shipped_qty;
3351             CLOSE c_orig_order_info;
3352 
3353             FOR old_adjustment_rec IN
3354                 c_orig_adjustment_amount (p_line_tbl (i).reference_line_id)
3355             LOOP
3356 
3357                IF l_shipped_qty is NOT NULL OR l_shipped_qty <> 0 THEN
3358                   l_adj_amount := old_adjustment_rec.amount * p_line_tbl(i).invoiced_quantity/ l_shipped_qty ;
3359                END IF;
3360 
3361                IF g_debug_flag = 'Y' THEN
3362                   ozf_utility_pvt.write_conc_log(' D: adjusted_changed_order: RMA with reference: l_adj_amount    ' || l_adj_amount);
3363                END IF;
3364 
3365                IF old_adjustment_rec.amount = 0 OR l_adj_amount = 0 THEN
3366                   GOTO l_endofloop;
3367                END IF;
3368 
3369                l_util_rec := l_empty_util_rec;
3370                l_act_budgets_rec :=l_empty_act_budgets_rec;
3371                l_act_budgets_rec.budget_source_type := 'OFFR';
3372                l_act_budgets_rec.budget_source_id := old_adjustment_rec.plan_id;
3373                l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3374                l_act_budgets_rec.act_budget_used_by_id := old_adjustment_rec.plan_id;
3375                l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
3376                l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
3377                l_util_rec.object_type := 'ORDER';
3378                l_util_rec.object_id   := p_line_tbl (i).header_id;
3379                l_util_rec.product_id := p_line_tbl(i).inventory_item_id;
3380                l_util_rec.price_adjustment_id := old_adjustment_rec.price_adjustment_id;
3381                l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
3382                l_util_rec.component_id :=old_adjustment_rec.plan_id;
3383                l_util_rec.component_type := 'OFFR';
3384                l_util_rec.currency_code :=old_adjustment_rec.currency_code;
3385                l_util_rec.fund_id :=old_adjustment_rec.fund_id;
3386                l_util_rec.order_line_id := p_line_tbl (i).line_id;
3387                l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;
3388                l_util_rec.gl_date := sysdate;
3389                l_act_budgets_rec.parent_src_apprvd_amt := l_adj_amount;
3390                l_act_budgets_rec.request_amount :=old_adjustment_rec.plan_curr_amount * p_line_tbl(i).invoiced_quantity/ l_shipped_qty ;
3391                l_util_rec.amount := l_adj_amount ;
3392                l_util_rec.plan_curr_amount :=  l_act_budgets_rec.request_amount;
3393                l_util_rec.adjustment_type_id :=-4;
3394                l_util_rec.adjustment_type := 'DECREASE_EARNED';
3395                l_util_rec.orig_utilization_id := old_adjustment_rec.orig_utilization_id;
3396 
3397                create_fund_utilization (
3398                         p_act_util_rec=> l_util_rec,
3399                         p_act_budgets_rec=> l_act_budgets_rec,
3400                         x_utilization_id => l_utilization_id,
3401                         x_return_status=> l_return_status,
3402                         x_msg_count=> x_msg_count,
3403                         x_msg_data=> x_msg_data
3404                );
3405 
3406                IF g_debug_flag = 'Y' THEN
3407                   ozf_utility_pvt.write_conc_log (
3408                        '    D: create utlization from RMA order: ' || l_return_status);
3409                END IF;
3410 
3411                IF l_return_status <> fnd_api.g_ret_sts_success THEN
3412                   GOTO l_endoflineadjloop;
3413                END IF;
3414                   --- quit when the total earned amount is adjusted
3415                <<l_endofloop>>
3416                NULL;
3417             END LOOP old_adjustment_rec;
3418          END IF; -- end of p_line_tbl (i).reference_line_id IS NOT NULL
3419 
3420          /*
3421            Note: adjustment already posted to TM budget in adjust_accrual when line is SHIPPED or RETURN order is booked
3422                  SHIPPED LINE: if shipped quantity <> requested quantity, e.g.
3423                  Original order: quantity 10, price adjustment id 12345
3424                  During shipping, only 8 are shipped, then 2 is backordered.
3425                  2 new lines are automatically created:
3426                  one line for shipped: quantity = 8, with old price adjustment id, line operation=UPDATE
3427                  another line for backorder: quantity = 2(10-8), with new price adjustment id, line operation=CREATE
3428 
3429                  handle case for partial ship with running accrual engine before ship. added by fliu on 05/24/04 to fix bug 3357164
3430                  If running accrual engine after booking order, one record is created. then partial shipped,  two new records will be created. one with positive
3431                  for backordered amount. another with negative for adjustment from previous record.
3432            */
3433 
3434           IF p_line_tbl(i).line_id= p_old_line_tbl(i).line_id
3435              AND p_old_line_tbl(i).ordered_quantity <>p_line_tbl(i).shipped_quantity
3436              AND NVL(p_line_tbl(i).shipped_quantity,0) <> 0
3437              --AND p_line_tbl(i).flow_status_code = 'SHIPPED'
3438           THEN
3439 
3440              IF g_debug_flag = 'Y' THEN
3441                 ozf_utility_pvt.write_conc_log('    D: adjusted_changed_order: partial shipment line(line_id=' || p_line_tbl(i).line_id || ')');
3442              END IF;
3443 
3444              OPEN c_order_info (p_line_tbl (i).header_id);
3445              FETCH c_order_info INTO l_order_status, l_order_booked_flag, l_order_curr,l_order_number,l_org_id;
3446              CLOSE c_order_info;
3447 
3448              FOR price_adjustment_rec IN c_all_price_adjustments (p_line_tbl (i).line_id)
3449              LOOP
3450 
3451                 OPEN c_old_adjustment_total_amount (price_adjustment_rec.price_adjustment_id);
3452                 FETCH c_old_adjustment_total_amount INTO l_total;
3453                 CLOSE c_old_adjustment_total_amount;
3454 
3455                 IF NVL(l_total,0) = 0 THEN  -- add to fix bug 4930867.
3456                    GOTO l_endpriceadjloop;
3457                 END IF;
3458 
3459                 FOR old_adjustment_rec IN
3460                     c_old_adjustment_amount(price_adjustment_rec.price_adjustment_id)
3461                 LOOP
3462                               -- adjust unshipped amount.
3463                     IF g_debug_flag = 'Y' THEN
3464                        ozf_utility_pvt.write_conc_log (' price_adjustment_rec.adjusted_amount: '|| price_adjustment_rec.adjusted_amount ||
3465                                                        ' p_line_tbl(i).shipped_quantity: '|| p_line_tbl(i).shipped_quantity ||
3466                                                        ' old_adjustment_rec.plan_curr_amount: '|| old_adjustment_rec.plan_curr_amount ||
3467                                                        ' price_adjustment_rec.price_adjustment_id: '|| price_adjustment_rec.price_adjustment_id );
3468                     END IF;
3469 
3470                     -- add by feliu on 08/03/04 to fix  3778200
3471                     IF old_adjustment_rec.utilization_type IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT') THEN  -- new calculation for adjustment.
3472                        l_orig_adj_amount := old_adjustment_rec.plan_curr_amount *
3473                                      (1 - p_line_tbl(i).shipped_quantity / p_old_line_tbl(i).ordered_quantity) ; -- in order currency.
3474                     ELSE
3475                         -- added by Ribha for bug fix 4417084
3476                        IF p_line_tbl(i).line_category_code <> 'RETURN' THEN
3477                           l_orig_adj_amount := old_adjustment_rec.plan_curr_amount -
3478                                              ( - price_adjustment_rec.adjusted_amount * p_line_tbl(i).shipped_quantity
3479                                              * old_adjustment_rec.plan_curr_amount /l_total) ; -- in order currency.
3480                        ELSE
3481                           l_orig_adj_amount := old_adjustment_rec.plan_curr_amount -
3482                                              ( - price_adjustment_rec.adjusted_amount * (-p_line_tbl(i).shipped_quantity)
3483                                                 * old_adjustment_rec.plan_curr_amount /l_total) ; -- in order currency.
3484                        END IF;
3485                     END IF;
3486 
3487                     IF g_debug_flag = 'Y' THEN
3488                        ozf_utility_pvt.write_conc_log (' partial ship l_total: '|| l_total ||
3489                                           ' partial ship p_line_tbl(i).shipped_quantity : '|| p_line_tbl(i).shipped_quantity  ||
3490                                           ' partial ship l_orig_adj_amount: '|| l_orig_adj_amount );
3491                     END IF;
3492 
3493                     l_orig_adj_amount  := ozf_utility_pvt.currround (
3494                                     l_orig_adj_amount ,
3495                                      l_order_curr
3496                                   ); -- in order  currency(same as offer currency)
3497 
3498                     IF l_order_curr <> old_adjustment_rec.currency_code THEN
3499                        ozf_utility_pvt.convert_currency(x_return_status => l_return_status
3500                                                         ,p_from_currency => l_order_curr
3501                                                         ,p_to_currency => old_adjustment_rec.currency_code
3502                                                         ,p_conv_type => old_adjustment_rec.exchange_rate_type --nirprasa Added for bug 7030415
3503                                                         ,p_from_amount =>l_orig_adj_amount
3504                                                         ,x_to_amount => l_adj_amount
3505                                                         ,x_rate => l_rate); -- in fund  currency
3506 
3507                     ELSE
3508                        l_adj_amount := l_orig_adj_amount;
3509                     END IF;
3510 
3511                     IF g_debug_flag = 'Y' THEN
3512                        ozf_utility_pvt.write_conc_log (' partial ship adj_amount: '|| l_adj_amount );
3513                     END IF;
3514 
3515                     IF NVL(l_adj_amount,0) = 0 THEN
3516                        GOTO l_endoffloop;
3517                     END IF;
3518 
3519                     l_util_rec := l_empty_util_rec;
3520                     l_act_budgets_rec :=l_empty_act_budgets_rec;
3521                     l_util_rec.object_type := 'ORDER';
3522                     l_util_rec.object_id   := p_line_tbl (i).header_id;
3523                     l_util_rec.product_id := p_line_tbl(i).inventory_item_id;
3524                     l_util_rec.price_adjustment_id := price_adjustment_rec.price_adjustment_id;
3525                     l_util_rec.utilization_type := old_adjustment_rec.utilization_type;
3526                     l_act_budgets_rec.budget_source_type := 'OFFR';
3527                     l_act_budgets_rec.budget_source_id := old_adjustment_rec.plan_id;
3528                     l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3529                     l_act_budgets_rec.act_budget_used_by_id := old_adjustment_rec.plan_id;
3530                     l_act_budgets_rec.parent_src_apprvd_amt := - l_adj_amount;
3531                     l_act_budgets_rec.parent_src_curr := old_adjustment_rec.currency_code;
3532                     l_act_budgets_rec.parent_source_id := old_adjustment_rec.fund_id;
3533                     l_act_budgets_rec.request_amount :=-l_orig_adj_amount;
3534                     l_act_budgets_rec.request_currency := l_order_curr;
3535                     l_util_rec.amount := - l_adj_amount ;
3536 
3537                     --kdass bug 5953774 convert amount from order currency to offer currency
3538                     OPEN c_offer_currency (old_adjustment_rec.plan_id);
3539                     FETCH c_offer_currency INTO l_offer_curr;
3540                     CLOSE c_offer_currency;
3541 
3542                     IF l_order_curr <> l_offer_curr THEN
3543                        ozf_utility_pvt.convert_currency(x_return_status => l_return_status
3544                                                         ,p_from_currency => l_order_curr
3545                                                         ,p_to_currency => l_offer_curr
3546                                                         ,p_conv_type => old_adjustment_rec.exchange_rate_type --nirprasa Added for bug 7030415
3547                                                         ,p_from_amount =>l_orig_adj_amount
3548                                                         ,x_to_amount => l_offer_amount
3549                                                         ,x_rate => l_rate); -- in offer  currency
3550 
3551                     ELSE
3552                        l_offer_amount := l_orig_adj_amount;
3553                     END IF;
3554 
3555                     l_util_rec.plan_curr_amount :=  - l_offer_amount;
3556 
3557                     l_util_rec.component_id :=old_adjustment_rec.plan_id;
3558                     l_util_rec.component_type := 'OFFR';
3559                     l_util_rec.currency_code :=old_adjustment_rec.currency_code;
3560                     l_util_rec.fund_id :=old_adjustment_rec.fund_id;
3561                     l_util_rec.order_line_id := p_line_tbl (i).line_id;
3562                     l_util_rec.gl_posted_flag := old_adjustment_rec.gl_posted_flag;  -- 'N';
3563                     -- create adjustment , added by feliu on 08/03/04 to fix bug 3778200
3564                     IF old_adjustment_rec.utilization_type  = 'ADJUSTMENT' THEN
3565                        l_util_rec.adjustment_type_id :=-4;
3566                        l_util_rec.adjustment_type := 'DECREASE_EARNED';
3567                        l_util_rec.orig_utilization_id := old_adjustment_rec.orig_utilization_id;
3568                     END IF;
3569 
3570                     create_fund_utilization (
3571                                      p_act_util_rec=> l_util_rec,
3572                                      p_act_budgets_rec=> l_act_budgets_rec,
3573                                      x_utilization_id => l_utilization_id,
3574                                      x_return_status=> l_return_status,
3575                                      x_msg_count=> x_msg_count,
3576                                     x_msg_data=> x_msg_data
3577                                   );
3578                     IF g_debug_flag = 'Y' THEN
3579                        ozf_utility_pvt.write_conc_log (' retrun status for create _fund_utilization of '|| l_return_status ||
3580                             ' when partial shipping. ' );
3581                     END IF;
3582 
3583                     IF l_return_status <> fnd_api.g_ret_sts_success THEN
3584                        GOTO l_endoflineadjloop;
3585                     END IF;
3586                     /* yzhao: fix bug 3778200 - partial shipment after offer adjustment.
3587                               if line is splitted to have new line for unshipped quantity, new price adjustment need to pass to the offer adjustment
3588                     */
3589                     /* adjustment should populate order_line_id */
3590                     IF old_adjustment_rec.utilization_type IN ('ADJUSTMENT', 'LEAD_ADJUSTMENT')  THEN
3591                        -- find out the corresponding new order line id and price adjustment id
3592                        -- create positive offer adjustment for unshipped quantity, no gl posting
3593                        -- and set new price adjustment id
3594                        OPEN c_split_line(p_line_tbl (i).line_id);
3595                        FETCH c_split_line INTO l_new_line_id;
3596                        CLOSE c_split_line;
3597 
3598                        OPEN c_new_adj_line(l_new_line_id,old_adjustment_rec.plan_id);
3599                        FETCH c_new_adj_line INTO l_new_adj_id;
3600                        CLOSE c_new_adj_line;
3601 
3602                        OPEN c_max_utilized_id(l_new_adj_id);
3603                        FETCH c_max_utilized_id INTO  l_util_rec.orig_utilization_id;
3604                        CLOSE c_max_utilized_id;
3605                        IF g_debug_flag = 'Y' THEN
3606                           ozf_utility_pvt.write_conc_log ('create positive line for adjustment: '|| l_new_adj_id );
3607                        END IF;
3608                        l_act_budgets_rec.request_amount := -l_act_budgets_rec.request_amount;
3609                        l_act_budgets_rec.parent_src_apprvd_amt := - l_act_budgets_rec.parent_src_apprvd_amt;
3610                        l_util_rec.amount := -l_util_rec.amount;
3611                        l_util_rec.plan_curr_amount := -l_util_rec.plan_curr_amount;
3612                        l_util_rec.order_line_id := l_new_line_id;
3613                        l_util_rec.price_adjustment_id := l_new_adj_id;
3614 
3615                        IF l_util_rec.utilization_type  = 'ADJUSTMENT' THEN
3616                           l_util_rec.adjustment_type_id :=-5;
3617                           l_util_rec.adjustment_type := 'STANDARD';
3618                        END IF;
3619 
3620                        create_fund_utilization (
3621                                          p_act_util_rec=> l_util_rec,
3622                                          p_act_budgets_rec=> l_act_budgets_rec,
3623                                          x_utilization_id => l_utilization_id,
3624                                          x_return_status=> l_return_status,
3625                                          x_msg_count=> x_msg_count,
3626                                         x_msg_data=> x_msg_data
3627                                       );
3628 
3629                        IF l_return_status <> fnd_api.g_ret_sts_success THEN
3630                           GOTO l_endoflineadjloop;
3631                        END IF;
3632 
3633                     END IF;-- end loop of old_adjustment_rec.utilization_type
3634                      --- quit when the total earned amount is adjusted
3635                     <<l_endoffloop>>
3636                     NULL;
3637                 END LOOP old_adjustment_rec;
3638                 <<l_endpriceadjloop>>
3639                 NULL;
3640              END LOOP; -- end loop for price adjustment rec
3641 
3642 
3643 
3644           END IF; -- end of shipped_quantity is not equal ordered_quantity.
3645 
3646           /*  yzhao: 12/02/2003 11.5.10 post to GL based on profile TM: Create GL Entries for Orders
3647               For normal order with accrual offer
3648                   a) if profile is set to 'Shipped', post to gl when line is shipped
3649                   b) if profile is set to 'Invoiced', post to gl when line is invoiced
3650               For normal order with off invoice offer that needs to post to gl
3651                or returned order,
3652                   post to gl when line is invoiced
3653            */
3654          l_gl_date := NULL;
3655 
3656          IF g_debug_flag = 'Y' THEN
3657             ozf_utility_pvt.write_conc_log ('    D: profile to create gl entries is set to ' ||
3658                     fnd_profile.VALUE ('OZF_ORDER_GLPOST_PHASE') || ' g_order_gl_phase=' || g_order_gl_phase);
3659          END IF;
3660 
3661          IF ( g_order_gl_phase = 'SHIPPED' AND p_line_tbl(i).line_category_code <> 'RETURN' AND
3662             NVL(p_line_tbl(i).shipped_quantity,0) <> 0 AND
3663             -- July 08 2004 fix bug 3746354 utilization missing for unshipped quantity after second partial shipment. add flow_status_code='SHIPPED'
3664             p_line_tbl(i).flow_status_code = 'SHIPPED') THEN
3665             OPEN c_actual_shipment_date(p_line_tbl(i).line_id);
3666             FETCH c_actual_shipment_date into l_gl_date ;
3667             CLOSE c_actual_shipment_date;
3668 
3669             l_sales_transaction_rec.quantity     := p_line_tbl(i).shipped_quantity;
3670             l_sales_transaction_rec.transfer_type := 'IN';
3671 
3672             IF g_debug_flag = 'Y' THEN
3673                ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() gl_date uses shipment date: ' || l_gl_date || ' for arrcual posting');
3674             END IF;
3675 
3676          END IF;
3677 
3678          IF l_order_number IS NULL THEN -- get order_number if null, bug fix 3917556
3679             OPEN c_order_info (p_line_tbl (i).header_id);
3680             FETCH c_order_info INTO l_order_status, l_order_booked_flag, l_order_curr,l_order_number,l_org_id;
3681             CLOSE c_order_info;
3682          END IF;
3683 
3684          IF l_gl_date IS NULL THEN
3685             IF (p_line_tbl(i).invoice_interface_status_code = 'YES' OR NVL(p_line_tbl(i).invoiced_quantity,0) <> 0) THEN
3686                OPEN c_invoice_date(p_line_tbl(i).line_id, l_order_number);
3687                FETCH c_invoice_date INTO l_gl_date;
3688                CLOSE c_invoice_date;
3689 
3690                IF l_gl_date IS NULL THEN
3691                     -- yzhao: Jun 29, 2004 if accrual engine runs before auto-invoice completes, invoice record not created in ar table
3692                   l_gl_date := sysdate;
3693                   IF g_debug_flag = 'Y' THEN
3694                      ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() auto-invoice not complete. use sysdate for gl_date');
3695                   END IF;
3696                END IF;
3697 
3698                l_sales_transaction_rec.quantity   := p_line_tbl(i).invoiced_quantity;
3699 
3700                IF g_debug_flag = 'Y' THEN
3701                   ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() gl_date uses invoice date: ' || l_gl_date || ' for arrcual posting');
3702                END IF;
3703             END IF;
3704          END IF;
3705 
3706          IF l_gl_date IS NOT NULL THEN
3707             OPEN sales_transation_csr(p_line_tbl (i).line_id);
3708             FETCH  sales_transation_csr INTO l_sales_trans;
3709             CLOSE sales_transation_csr;
3710 
3711             IF g_debug_flag = 'Y' THEN
3712                ozf_utility_pvt.write_conc_log('    Create_Transaction: l_sales_trans:  ' ||  l_sales_trans);
3713             END IF;
3714 
3715             IF NVL(l_sales_trans,0) <> 1 THEN
3716 
3717                l_sales_transaction_rec.sold_to_cust_account_id := p_line_tbl (i).sold_to_org_id;
3718 
3719                OPEN party_id_csr(l_sales_transaction_rec.sold_to_cust_account_id);
3720                FETCH party_id_csr INTO l_sales_transaction_rec.sold_to_party_id;
3721                CLOSE party_id_csr;
3722 
3723                OPEN party_site_id_csr(p_line_tbl (i).invoice_to_org_id);
3724                FETCH party_site_id_csr INTO l_sales_transaction_rec.sold_to_party_site_id;
3725                CLOSE party_site_id_csr;
3726 
3727                l_sales_transaction_rec.ship_to_site_use_id  := p_line_tbl (i).ship_to_org_id;
3728                l_sales_transaction_rec.bill_to_site_use_id  :=p_line_tbl(i).invoice_to_org_id;
3729                l_sales_transaction_rec.uom_code:= NVL(p_line_tbl(i).shipping_quantity_uom,p_line_tbl(i).order_quantity_uom);
3730                l_sales_transaction_rec.amount   := p_line_tbl(i).unit_selling_price * l_sales_transaction_rec.quantity;
3731                l_sales_transaction_rec.currency_code  :=l_order_curr;
3732                l_sales_transaction_rec.inventory_item_id := p_line_tbl(i).inventory_item_id;
3733                l_sales_transaction_rec.header_id  :=   p_line_tbl (i).header_id;
3734                l_sales_transaction_rec.line_id  := p_line_tbl (i).line_id;
3735                l_sales_transaction_rec.source_code := 'OM';
3736                IF p_line_tbl(i).line_category_code <> 'RETURN' THEN
3737                   l_sales_transaction_rec.transfer_type := 'IN';
3738                ELSE
3739                   l_sales_transaction_rec.transfer_type := 'OUT';
3740                END IF;
3741                l_sales_transaction_rec.transaction_date  := l_gl_date;--l_volume_detail_rec.transaction_date
3742                l_sales_transaction_rec.org_id := l_org_id;
3743 
3744                IF g_debug_flag = 'Y' THEN
3745                   ozf_utility_pvt.write_conc_log('   Create_Transaction' );
3746                END IF;
3747 
3748                OZF_SALES_TRANSACTIONS_PVT.Create_Transaction (
3749                                p_api_version      => 1.0
3750                               ,p_init_msg_list    => FND_API.G_FALSE
3751                               ,p_commit           => FND_API.G_FALSE
3752                               ,p_validation_level => FND_API.G_VALID_LEVEL_FULL
3753                               ,p_transaction_rec  => l_sales_transaction_rec
3754                               ,x_sales_transaction_id => l_sales_transaction_id
3755                               ,x_return_status    => l_return_status
3756                               ,x_msg_data         => x_msg_data
3757                               ,x_msg_count        => x_msg_count
3758                       );
3759 
3760                IF g_debug_flag = 'Y' THEN
3761                   ozf_utility_pvt.write_conc_log('   Create_Transaction' ||  l_return_status);
3762                END IF;
3763 
3764                IF l_return_status <> fnd_api.g_ret_sts_success THEN
3765                   GOTO l_endoflineadjloop;
3766                END IF;
3767             END IF; -- NVL(l_sales_trans,0)
3768 
3769             OPEN c_get_accrual_rec(p_line_tbl(i).line_id);
3770             LOOP
3771                FETCH c_get_accrual_rec BULK COLLECT
3772                INTO l_utilIdTbl, l_objVerTbl, l_planTypeTbl, l_utilTypeTbl, l_amountTbl
3773                     , l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
3774                LIMIT g_bulk_limit;
3775 
3776                FORALL t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
3777                UPDATE ozf_funds_utilized_all_b
3778                SET gl_date = l_gl_date
3779                WHERE utilization_id = l_utilIdTbl(t_i);
3780 
3781                FOR t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
3782                LOOP
3783                   post_accrual_to_gl(        p_util_utilization_id          => l_utilIdTbl(t_i)
3784                                            , p_util_object_version_number => l_objVerTbl(t_i)
3785                                            , p_util_amount                => l_amountTbl(t_i)
3786                                            , p_util_plan_type             => l_planTypeTbl(t_i)
3787                                            , p_util_plan_id               => l_planIdTbl(t_i)
3788                                            , p_util_plan_amount           => l_planAmtTbl(t_i)
3789                                            , p_util_utilization_type      => l_utilTypeTbl(t_i)
3790                                            , p_util_fund_id               => l_fundIdTbl(t_i)
3791                                            , p_util_acctd_amount          => l_acctAmtTbl(t_i)
3792                                            , p_util_org_id                => l_orgIdTbl(t_i)
3793                                            , x_gl_posted_flag             => l_gl_posted_flag
3794                                            , x_return_status              => l_return_status
3795                                            , x_msg_count                  => x_msg_count
3796                                            , x_msg_data                   => x_msg_data
3797                                        );
3798 
3799                          -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
3800                   IF g_debug_flag = 'Y' THEN
3801                      ozf_utility_pvt.write_conc_log('    D: adjust_changed_order() processing invoiced/shipped line ' || p_line_tbl(i).line_id
3802                              || '  post_accrual_to_gl(util_id=' || l_utilIdTbl(t_i) || ') returns ' || l_return_status
3803                              || '  x_gl_posted_flag=' || l_gl_posted_flag);
3804                   END IF;
3805                          -- yzhao: 03/04/2004 post gl for related accruals from offer adjustment or object reconcile
3806                   IF l_return_status = fnd_api.g_ret_sts_success AND l_gl_posted_flag = G_GL_FLAG_YES THEN
3807                      post_related_accrual_to_gl(
3808                                 p_utilization_id              => l_utilIdTbl(t_i)
3809                               , p_utilization_type            => l_utilTypeTbl(t_i)
3810                               , p_gl_date                     => l_gl_date
3811                               , x_return_status               => l_return_status
3812                               , x_msg_count                   => x_msg_count
3813                               , x_msg_data                    => x_msg_data
3814                            );
3815                   END IF;
3816                 END LOOP; -- FOR t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
3817 
3818                 EXIT WHEN c_get_accrual_rec%NOTFOUND;
3819             END LOOP;  -- bulk fetch
3820             CLOSE c_get_accrual_rec;
3821 
3822          END IF;  -- IF l_gl_date IS NOT NULL
3823 
3824          <<l_endoflineadjloop>>
3825          IF l_return_status <> fnd_api.g_ret_sts_success THEN
3826             -- Write Relelvant Messages
3827             IF g_debug_flag = 'Y' THEN
3828                 ozf_utility_pvt.write_conc_log (
3829                ' /*************************** DEBUG MESSAGE END *************************/' ||
3830                ' /****** Offer Adjustment For Line(id=' || p_line_tbl(i).line_id || ') failed  with the following Errors *******/');
3831             END IF;
3832 
3833             -- Dump All the MEssages from the Message list
3834             ozf_utility_pvt.write_conc_log;
3835             -- Initialize the Message list for NExt Processing
3836             fnd_msg_pub.initialize;
3837             ROLLBACK TO line_adjustment;
3838             -- return a status error
3839             x_return_status := fnd_api.g_ret_sts_error ;
3840             --5/30/2002  Added to exit the loop because we want to perform handle exception to put the  me
3841             -- go out of the loop because we put this message in the exception queue
3842             EXIT;
3843          ELSIF  l_return_status = fnd_api.g_ret_sts_success THEN
3844             IF g_debug_flag = 'Y' THEN
3845                ozf_utility_pvt.write_conc_log (' /*************************** DEBUG MESSAGE END *********************/'||
3846                    ' /****** Line Adjustment Success *******/ p_line_tbl(i).line_id  '   || p_line_tbl(i).line_id );
3847             END IF;
3848          ELSE
3849            IF g_debug_flag = 'Y' THEN
3850               ozf_utility_pvt.write_conc_log ( '    D: Line Return Status ' ||l_return_status);
3851            END IF;
3852 
3853          END IF;
3854 
3855       END LOOP new_line_tbl_loop;
3856 
3857       -- Standard call to get message count and IF count is 1, get message info.
3858       fnd_msg_pub.count_and_get (
3859          p_count=> x_msg_count,
3860          p_data=> x_msg_data,
3861          p_encoded=> fnd_api.g_false
3862       );
3863    EXCEPTION
3864       WHEN OTHERS THEN
3865          --ROLLBACK TO adjust_accrual;
3866          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3867          ozf_utility_pvt.write_conc_log (' /**************UNEXPECTED EXCEPTION*************/');
3868          ozf_utility_pvt.write_conc_log('    D: adjust_changed_order: exception. errcode=' || sqlcode || '  msg: ' || substr(sqlerrm, 1, 3000));
3869 
3870          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3871             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
3872          END IF;
3873          fnd_msg_pub.count_and_get (
3874             p_count=> x_msg_count,
3875             p_data=> x_msg_data,
3876             p_encoded=> fnd_api.g_false
3877          );
3878    END adjust_changed_order;
3879 
3880    ------------------------------------------------------------------------------
3881 -- Procedure Name
3882 --   Get_Exception_Message
3883 -- Purpose
3884 --   This procedure collects order updates FROM the Order Capture NotIFication
3885 --   API. Started FROM a concurrent process, it is a loop which
3886 --   gets the latest notIFication off of the queue.
3887 --
3888 -- History
3889 --   4/30/2002 mpande Created
3890 ------------------------------------------------------------------------------
3891    PROCEDURE get_exception_message (x_errbuf OUT NOCOPY VARCHAR2, x_retcode OUT NUMBER);
3892 ------------------------------------------------------------------------------
3893 -- Procedure Name
3894 --   Get_Message
3895 -- Purpose
3896 --   This procedure collects order updates FROM the Order Capture NotIFication
3897 --   API. Started FROM a concurrent process, it is a loop which
3898 --   gets the latest notIFication off of the queue.
3899 --   p_run_exception IN VARCHAR2
3900 --    Can Have 2 values : 'N' Run Only Messages Donot Run Exception Messages
3901 --                      : 'Y' Run Both Message and Exception  DEFAULT
3902 -- History
3903 --   06-20-00  pjindal Created
3904 --   06-20-00  updated message handling and error handling
3905 --   5/6/2002  Added one more parameter to run exception messages
3906 ------------------------------------------------------------------------------
3907    PROCEDURE get_message (x_errbuf OUT NOCOPY VARCHAR2,
3908                           x_retcode OUT NOCOPY NUMBER,
3909                           p_run_exception IN VARCHAR2 := 'N',
3910                           p_debug     IN VARCHAR2 := 'N'
3911                          ) IS
3912       l_return_status              VARCHAR2 (1);
3913       l_process_audit_id           NUMBER;
3914       l_msg_count                  NUMBER;
3915       l_msg_data                   VARCHAR2 (2000);
3916       l_no_more_messages           VARCHAR2 (1);
3917       l_header_id                  NUMBER;
3918       l_booked_flag                VARCHAR2 (1);
3919       l_header_rec                 oe_order_pub.header_rec_type;
3920       l_old_header_rec             oe_order_pub.header_rec_type;
3921       l_header_adj_tbl             oe_order_pub.header_adj_tbl_type;
3922       l_old_header_adj_tbl         oe_order_pub.header_adj_tbl_type;
3923       l_header_price_att_tbl       oe_order_pub.header_price_att_tbl_type;
3924       l_old_header_price_att_tbl   oe_order_pub.header_price_att_tbl_type;
3925       l_header_adj_att_tbl         oe_order_pub.header_adj_att_tbl_type;
3926       l_old_header_adj_att_tbl     oe_order_pub.header_adj_att_tbl_type;
3927       l_header_adj_assoc_tbl       oe_order_pub.header_adj_assoc_tbl_type;
3928       l_old_header_adj_assoc_tbl   oe_order_pub.header_adj_assoc_tbl_type;
3929       l_header_scredit_tbl         oe_order_pub.header_scredit_tbl_type;
3930       l_old_header_scredit_tbl     oe_order_pub.header_scredit_tbl_type;
3931       l_line_tbl                   oe_order_pub.line_tbl_type;
3932       l_old_line_tbl               oe_order_pub.line_tbl_type;
3933       l_line_adj_tbl               oe_order_pub.line_adj_tbl_type;
3934       l_old_line_adj_tbl           oe_order_pub.line_adj_tbl_type;
3935       l_line_price_att_tbl         oe_order_pub.line_price_att_tbl_type;
3936       l_old_line_price_att_tbl     oe_order_pub.line_price_att_tbl_type;
3937       l_line_adj_att_tbl           oe_order_pub.line_adj_att_tbl_type;
3938       l_old_line_adj_att_tbl       oe_order_pub.line_adj_att_tbl_type;
3939       l_line_adj_assoc_tbl         oe_order_pub.line_adj_assoc_tbl_type;
3940       l_old_line_adj_assoc_tbl     oe_order_pub.line_adj_assoc_tbl_type;
3941       l_line_scredit_tbl           oe_order_pub.line_scredit_tbl_type;
3942       l_old_line_scredit_tbl       oe_order_pub.line_scredit_tbl_type;
3943       l_lot_serial_tbl             oe_order_pub.lot_serial_tbl_type;
3944       l_old_lot_serial_tbl         oe_order_pub.lot_serial_tbl_type;
3945       l_action_request_tbl         oe_order_pub.request_tbl_type;
3946       l_que_msg_count              NUMBER := 0 ;
3947    BEGIN
3948       -- Standard Start of process savepoint
3949       -- Start looping to check for messages in the queue
3950       fnd_msg_pub.initialize;
3951       g_debug_flag := p_debug ;
3952 
3953       SAVEPOINT get_message_savepoint;
3954 
3955       <<message_loop>>
3956 
3957       LOOP
3958          -- Queue savepoint for standard advanced queue error handling
3959          BEGIN
3960          SAVEPOINT get_message_loop_savepoint;
3961 
3962          ozf_utility_pvt.write_conc_log ('STARTING MESSAGE QUEUE');
3963 
3964          --
3965          -- Invoke Get_Mesage to dequeue queue payload and return Order data
3966          --
3967          aso_order_feedback_pub.get_notice (
3968             p_api_version=> 1.0,
3969             x_return_status=> l_return_status,
3970             x_msg_count=> l_msg_count,
3971             x_msg_data=> l_msg_data,
3972             p_app_short_name=> 'OZF' -- need to be resolved , wether it is AMS or OZF
3973                                     ,
3974             x_no_more_messages=> l_no_more_messages,
3975             x_header_rec=> l_header_rec,
3976             x_old_header_rec=> l_old_header_rec,
3977             x_header_adj_tbl=> l_header_adj_tbl,
3978             x_old_header_adj_tbl=> l_old_header_adj_tbl,
3979             x_header_price_att_tbl=> l_header_price_att_tbl,
3980             x_old_header_price_att_tbl=> l_old_header_price_att_tbl,
3981             x_header_adj_att_tbl=> l_header_adj_att_tbl,
3982             x_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
3983             x_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
3984             x_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
3985             x_header_scredit_tbl=> l_header_scredit_tbl,
3986             x_old_header_scredit_tbl=> l_old_header_scredit_tbl,
3987             x_line_tbl=> l_line_tbl,
3988             x_old_line_tbl=> l_old_line_tbl,
3989             x_line_adj_tbl=> l_line_adj_tbl,
3990             x_old_line_adj_tbl=> l_old_line_adj_tbl,
3991             x_line_price_att_tbl=> l_line_price_att_tbl,
3992             x_old_line_price_att_tbl=> l_old_line_price_att_tbl,
3993             x_line_adj_att_tbl=> l_line_adj_att_tbl,
3994             x_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
3995             x_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
3996             x_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
3997             x_line_scredit_tbl=> l_line_scredit_tbl,
3998             x_old_line_scredit_tbl=> l_old_line_scredit_tbl,
3999             x_lot_serial_tbl=> l_lot_serial_tbl,
4000             x_old_lot_serial_tbl=> l_old_lot_serial_tbl,
4001             x_action_request_tbl=> l_action_request_tbl
4002          );
4003          --
4004          --///added by mpande to write a error message to the list
4005          --if not sucess add a error message to th emessage listx
4006          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
4007             ozf_utility_pvt.write_conc_log ('Queue Return Error ');
4008 
4009             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
4010                fnd_message.set_name ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK_FAIL');
4011                fnd_msg_pub.ADD;
4012             END IF;
4013             ozf_utility_pvt.write_conc_log;
4014             RETURN;
4015          END IF;
4016          -- Check return status
4017          -- if success call adjust_accrual
4018          --
4019          IF l_return_status = fnd_api.g_ret_sts_success THEN
4020             IF (l_line_adj_tbl.COUNT <> 0) THEN
4021                IF g_debug_flag = 'Y' THEN
4022                   ozf_utility_pvt.write_conc_log ('ADJUSTMENT ');
4023                END IF;
4024 
4025                adjust_accrual (
4026                   p_api_version=> 1.0
4027                  ,p_init_msg_list=> fnd_api.g_true
4028                  ,x_return_status=> l_return_status
4029                  ,x_msg_count=> l_msg_count
4030                  ,x_msg_data=> l_msg_data
4031                  ,p_line_adj_tbl=> l_line_adj_tbl
4032                  ,p_old_line_adj_tbl=> l_old_line_adj_tbl
4033                  ,p_header_rec=> l_header_rec
4034                );
4035                IF g_debug_flag = 'Y' THEN
4036                   ozf_utility_pvt.write_conc_log (   'ADJUSTMENT STATUS ' || l_return_status);
4037                END IF;
4038             END IF;
4039          END IF;
4040          --l_return_status := fnd_api.g_ret_sts_success;
4041          IF l_return_status = fnd_api.g_ret_sts_success THEN
4042             IF (l_line_tbl.COUNT <> 0) THEN
4043                IF g_debug_flag = 'Y' THEN
4044                   ozf_utility_pvt.write_conc_log ('LINE');
4045                END IF;
4046                adjust_changed_order (
4047                   p_api_version=> 1.0
4048                  ,p_init_msg_list=> fnd_api.g_true
4049                  ,x_return_status=> l_return_status
4050                  ,x_msg_count=> l_msg_count
4051                  ,x_msg_data=> l_msg_data
4052                  ,p_header_rec=> l_header_rec
4053                  ,p_old_header_rec=> l_old_header_rec
4054                  ,p_line_tbl=> l_line_tbl
4055                  ,p_old_line_tbl=> l_old_line_tbl
4056                );
4057                IF g_debug_flag = 'Y' THEN
4058                   ozf_utility_pvt.write_conc_log (                 'LINE STATUS '          || l_return_status       );
4059                END IF;
4060             END IF;
4061          END IF;
4062        -- Call to Volume Offer adjustment.
4063         --
4064 
4065          IF l_no_more_messages = 'T' THEN
4066             ozf_utility_pvt.write_conc_log (   'NO MORE MESSAGES IN THE QUEUE ' || l_no_more_messages);
4067          END IF;
4068          --
4069          -- Check return status of functional process,
4070          -- rollback to undo processing
4071          -- if not success write the error message to the log file
4072 
4073          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
4074             --fnd_file.put_line(--fnd_file.log, 'before writinf concurrenct log '||l_return_status);
4075             ozf_utility_pvt.write_conc_log ('D: Error in one of the process');
4076 
4077             ROLLBACK TO get_message_loop_savepoint;
4078             x_retcode                  := 1;
4079             x_errbuf                   := l_msg_data;
4080          END IF;
4081 
4082          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
4083             /*Enqueue the failed message into the Order Feedback Exception Queue. This data
4084             can be dequeued subsequently by using the GET_EXCEPTION API */
4085             IF g_debug_flag = 'Y' THEN
4086                ozf_utility_pvt.write_conc_log ('In handle queue exception ');
4087             END IF;
4088             aso_order_feedback_pub.handle_exception (
4089                p_api_version=> 1.0,
4090                p_init_msg_list=> fnd_api.g_false,
4091                p_commit=> fnd_api.g_false,
4092                x_return_status=> l_return_status,
4093                x_msg_count=> l_msg_count,
4094                x_msg_data=> l_msg_data,
4095                p_app_short_name=> 'OZF',
4096                p_header_rec=> l_header_rec,
4097                p_old_header_rec=> l_old_header_rec,
4098                p_header_adj_tbl=> l_header_adj_tbl,
4099                p_old_header_adj_tbl=> l_old_header_adj_tbl,
4100                p_header_price_att_tbl=> l_header_price_att_tbl,
4101                p_old_header_price_att_tbl=> l_old_header_price_att_tbl,
4102                p_header_adj_att_tbl=> l_header_adj_att_tbl,
4103                p_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
4104                p_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
4105                p_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
4106                p_header_scredit_tbl=> l_header_scredit_tbl,
4107                p_old_header_scredit_tbl=> l_old_header_scredit_tbl,
4108                p_line_tbl=> l_line_tbl,
4109                p_old_line_tbl=> l_old_line_tbl,
4110                p_line_adj_tbl=> l_line_adj_tbl,
4111                p_old_line_adj_tbl=> l_old_line_adj_tbl,
4112                p_line_price_att_tbl=> l_line_price_att_tbl,
4113                p_old_line_price_att_tbl=> l_old_line_price_att_tbl,
4114                p_line_adj_att_tbl=> l_line_adj_att_tbl,
4115                p_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
4116                p_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
4117                p_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
4118                p_line_scredit_tbl=> l_line_scredit_tbl,
4119                p_old_line_scredit_tbl=> l_old_line_scredit_tbl,
4120                p_lot_serial_tbl=> l_lot_serial_tbl,
4121                p_old_lot_serial_tbl=> l_old_lot_serial_tbl,
4122                p_action_request_tbl=> l_action_request_tbl
4123             );
4124          END IF;
4125          -- Quit the procedure IF the queue is empty
4126          ozf_utility_pvt.write_conc_log (' /*************************** END OF QUEUE MESSAGE  *************************/');
4127 
4128          EXIT WHEN l_return_status = fnd_api.g_ret_sts_unexp_error;
4129          EXIT WHEN l_no_more_messages = fnd_api.g_true;
4130          l_que_msg_count := l_que_msg_count + 1 ;
4131          IF l_return_status = fnd_api.g_ret_sts_success THEN
4132             COMMIT;
4133             x_retcode                  := 0;
4134          END IF;
4135          EXCEPTION
4136          WHEN FND_API.G_EXC_ERROR THEN
4137             ROLLBACK TO get_message_loop_savepoint;
4138             ozf_utility_pvt.write_conc_log('FALIED');
4139             ozf_utility_pvt.write_conc_log;
4140 
4141         WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
4142             ROLLBACK TO get_message_loop_savepoint;
4143             ozf_utility_pvt.write_conc_log('FALIED');
4144             ozf_utility_pvt.write_conc_log;
4145 
4146         WHEN OTHERS THEN
4147             ROLLBACK TO get_message_loop_savepoint;
4148             ozf_utility_pvt.write_conc_log('FAILED');
4149             IF FND_MSG_PUB.Check_Msg_level (FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW) THEN
4150                FND_MESSAGE.Set_Name('OZF','OZF_API_DEBUG_MESSAGE');
4151                FND_MESSAGE.Set_Token('TEXT',sqlerrm);
4152                FND_MSG_PUB.Add;
4153             END IF;
4154             ozf_utility_pvt.write_conc_log;
4155 
4156          END;
4157       END LOOP message_loop;
4158 
4159       ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED '|| to_char(l_que_msg_count) || ' MESSAGES ');
4160       -- move except message from begining to last to fix issue for double creating accrual when same messsages
4161       -- in both exception queue and normal queue. by feliu on 12/30/2005
4162       IF p_run_exception = 'Y' THEN
4163 
4164          ozf_utility_pvt.write_conc_log ('START Exception Message ....... '|| x_retcode);
4165 
4166          ozf_utility_pvt.write_conc_log ('<====EXCEPTION QUEUE START TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4167 
4168          get_exception_message(x_errbuf , x_retcode);
4169 
4170          ozf_utility_pvt.write_conc_log ('END Exception Message Return Code'|| x_retcode);
4171 
4172          ozf_utility_pvt.write_conc_log ('<====EXCEPTION QUEUE END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4173 
4174       END IF;
4175 
4176 
4177    EXCEPTION
4178       WHEN fnd_api.g_exc_error THEN
4179         ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED ' ||to_char(l_que_msg_count) ||'MESSAGES' );
4180         x_retcode := 1;
4181       WHEN fnd_api.g_exc_unexpected_error THEN
4182         ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED ' ||to_char(l_que_msg_count) || 'MESSAGES' );
4183         x_retcode := 1;
4184       WHEN OTHERS THEN
4185         ozf_utility_pvt.write_conc_log ('QUEUE PROCESSED '|| to_char(l_que_msg_count) ||'MESSAGES' );
4186         x_retcode := 1;
4187 
4188    END get_message;
4189    ------------------------------------------------------------------------------
4190 -- Procedure Name
4191 --   Get_Exception_Message
4192 -- Purpose
4193 --   This procedure collects order updates FROM the Order Capture NotIFication
4194 --   API. Started FROM a concurrent process, it is a loop which
4195 --   gets the latest notIFication off of the queue.
4196 --
4197 -- History
4198 --   4/30/2002 mpande Created
4199 ------------------------------------------------------------------------------
4200    PROCEDURE get_exception_message (x_errbuf OUT NOCOPY VARCHAR2,
4201                                     x_retcode OUT NOCOPY NUMBER
4202    )  IS
4203       l_return_status              VARCHAR2 (1);
4204       l_process_audit_id           NUMBER;
4205       l_msg_count                  NUMBER;
4206       l_msg_data                   VARCHAR2 (2000);
4207       l_no_more_messages           VARCHAR2 (1);
4208       l_header_id                  NUMBER;
4209       l_booked_flag                VARCHAR2 (1);
4210       l_header_rec                 oe_order_pub.header_rec_type;
4211       l_old_header_rec             oe_order_pub.header_rec_type;
4212       l_header_adj_tbl             oe_order_pub.header_adj_tbl_type;
4213       l_old_header_adj_tbl         oe_order_pub.header_adj_tbl_type;
4214       l_header_price_att_tbl       oe_order_pub.header_price_att_tbl_type;
4215       l_old_header_price_att_tbl   oe_order_pub.header_price_att_tbl_type;
4216       l_header_adj_att_tbl         oe_order_pub.header_adj_att_tbl_type;
4217       l_old_header_adj_att_tbl     oe_order_pub.header_adj_att_tbl_type;
4218       l_header_adj_assoc_tbl       oe_order_pub.header_adj_assoc_tbl_type;
4219       l_old_header_adj_assoc_tbl   oe_order_pub.header_adj_assoc_tbl_type;
4220       l_header_scredit_tbl         oe_order_pub.header_scredit_tbl_type;
4221       l_old_header_scredit_tbl     oe_order_pub.header_scredit_tbl_type;
4222       l_line_tbl                   oe_order_pub.line_tbl_type;
4223       l_old_line_tbl               oe_order_pub.line_tbl_type;
4224       l_line_adj_tbl               oe_order_pub.line_adj_tbl_type;
4225       l_old_line_adj_tbl           oe_order_pub.line_adj_tbl_type;
4226       l_line_price_att_tbl         oe_order_pub.line_price_att_tbl_type;
4227       l_old_line_price_att_tbl     oe_order_pub.line_price_att_tbl_type;
4228       l_line_adj_att_tbl           oe_order_pub.line_adj_att_tbl_type;
4229       l_old_line_adj_att_tbl       oe_order_pub.line_adj_att_tbl_type;
4230       l_line_adj_assoc_tbl         oe_order_pub.line_adj_assoc_tbl_type;
4231       l_old_line_adj_assoc_tbl     oe_order_pub.line_adj_assoc_tbl_type;
4232       l_line_scredit_tbl           oe_order_pub.line_scredit_tbl_type;
4233       l_old_line_scredit_tbl       oe_order_pub.line_scredit_tbl_type;
4234       l_lot_serial_tbl             oe_order_pub.lot_serial_tbl_type;
4235       l_old_lot_serial_tbl         oe_order_pub.lot_serial_tbl_type;
4236       l_action_request_tbl         oe_order_pub.request_tbl_type;
4237       l_index   NUMBER;
4238       l_mode                       VARCHAR2(30):= DBMS_AQ.BROWSE;
4239       l_navigation                 VARCHAR2 (30) := DBMS_AQ.FIRST_MESSAGE;
4240 
4241    BEGIN
4242       -- Standard Start of process savepoint
4243       -- Start looping to check for messages in the queue
4244       fnd_msg_pub.initialize;
4245       SAVEPOINT get_message_savepoint;
4246       -- dequeue the exception queue
4247       <<exception_loop>>
4248       LOOP
4249          ozf_utility_pvt.write_conc_log ('In Queue Exception ');
4250 
4251          -- Queue savepoint for standard advanced queue error handling
4252          BEGIN
4253          SAVEPOINT get_excep_loop_savepoint;
4254          --
4255          -- Invoke Get_Mesage to dequeue queue payload and return Order data
4256          --
4257          aso_order_feedback_pub.get_exception (
4258             p_api_version=> 1.0,
4259             x_return_status=> l_return_status,
4260             x_msg_count=> l_msg_count,
4261             x_msg_data=> l_msg_data,
4262             p_app_short_name=> 'OZF', -- need to be resolved , wether it is AMS or OZF
4263             p_dequeue_mode  => l_mode,
4264             p_navigation   => l_navigation ,
4265             x_no_more_messages=> l_no_more_messages,
4266             x_header_rec=> l_header_rec,
4267             x_old_header_rec=> l_old_header_rec,
4268             x_header_adj_tbl=> l_header_adj_tbl,
4269             x_old_header_adj_tbl=> l_old_header_adj_tbl,
4270             x_header_price_att_tbl=> l_header_price_att_tbl,
4271             x_old_header_price_att_tbl=> l_old_header_price_att_tbl,
4272             x_header_adj_att_tbl=> l_header_adj_att_tbl,
4273             x_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
4274             x_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
4275             x_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
4276             x_header_scredit_tbl=> l_header_scredit_tbl,
4277             x_old_header_scredit_tbl=> l_old_header_scredit_tbl,
4278             x_line_tbl=> l_line_tbl,
4279             x_old_line_tbl=> l_old_line_tbl,
4280             x_line_adj_tbl=> l_line_adj_tbl,
4281             x_old_line_adj_tbl=> l_old_line_adj_tbl,
4282             x_line_price_att_tbl=> l_line_price_att_tbl,
4283             x_old_line_price_att_tbl=> l_old_line_price_att_tbl,
4284             x_line_adj_att_tbl=> l_line_adj_att_tbl,
4285             x_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
4286             x_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
4287             x_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
4288             x_line_scredit_tbl=> l_line_scredit_tbl,
4289             x_old_line_scredit_tbl=> l_old_line_scredit_tbl,
4290             x_lot_serial_tbl=> l_lot_serial_tbl,
4291             x_old_lot_serial_tbl=> l_old_lot_serial_tbl,
4292             x_action_request_tbl=> l_action_request_tbl
4293          );
4294          --
4295          --ozf_utility_pvt.debug_message('l_return_status  ='||l_return_status );
4296          --///added by mpande to write a error message to the list
4297          --if not sucess add a error message to th emessage list
4298          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
4299              IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
4300                fnd_message.set_name ('OZF', 'OZF_FUND_ASO_ORD_FEEDBACK_FAIL');
4301                fnd_msg_pub.ADD;
4302             END IF;
4303             ozf_utility_pvt.write_conc_log;
4304             RETURN;
4305          END IF;
4306          -- Check return status
4307          -- if success call adjust_accrual
4308          --
4309          IF l_return_status = fnd_api.g_ret_sts_success THEN
4310             IF (l_line_adj_tbl.COUNT <> 0) THEN
4311                 ozf_utility_pvt.write_conc_log ('In get exception adjustment');
4312 
4313                adjust_accrual (
4314                   p_api_version=> 1.0,
4315                   p_init_msg_list=> fnd_api.g_true,
4316                   x_return_status=> l_return_status,
4317                   x_msg_count=> l_msg_count,
4318                   x_msg_data=> l_msg_data,
4319                   p_line_adj_tbl=> l_line_adj_tbl,
4320                   p_old_line_adj_tbl=> l_old_line_adj_tbl,
4321                   p_header_rec=> l_header_rec,
4322                   p_exception_queue    => fnd_api.g_true
4323                );
4324                ozf_utility_pvt.write_conc_log ('ADJUSTMENT EXCEPTION STATUS'||l_return_status);
4325 
4326             END IF;
4327          END IF;
4328          IF l_return_status = fnd_api.g_ret_sts_success THEN
4329             IF (l_line_tbl.COUNT <> 0) THEN
4330                ozf_utility_pvt.write_conc_log ('    D: EXCEPTON QUEUE Start processing line');
4331 
4332                adjust_changed_order (
4333                   p_api_version=> 1.0,
4334                   p_init_msg_list=> fnd_api.g_true,
4335                   x_return_status=> l_return_status,
4336                   x_msg_count=> l_msg_count,
4337                   x_msg_data=> l_msg_data,
4338                   p_header_rec=> l_header_rec,
4339                   p_old_header_rec=> l_old_header_rec,
4340                   p_line_tbl=> l_line_tbl,
4341                   p_old_line_tbl=> l_old_line_tbl
4342                );
4343                ozf_utility_pvt.write_conc_log ('    D: EXCEPTION QUEUE PROCESSING LINE RETURNS STATUS'||l_return_status);
4344 
4345             END IF;
4346          END IF;
4347 
4348          IF l_no_more_messages = 'T' THEN
4349             ozf_utility_pvt.write_conc_log (   'NO MORE MESSAGES IN THE QUEUE '
4350                                          || l_no_more_messages);
4351          END IF;
4352          -- write_conc_log;
4353          --
4354          -- Check return status of functional process,
4355          -- rollback to undo processing
4356          -- if not success write the error message to the log file
4357          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
4358             l_navigation  := DBMS_AQ.NEXT_MESSAGE;
4359             ROLLBACK TO get_excep_loop_savepoint;
4360             --x_retcode                  := 1;
4361             x_errbuf                   := l_msg_data;
4362          END IF;
4363          -- Quit the procedure IF the queue is empty
4364          EXIT WHEN l_return_status = fnd_api.g_ret_sts_unexp_error;
4365          EXIT WHEN l_no_more_messages = fnd_api.g_true;
4366 
4367          IF l_return_status = fnd_api.g_ret_sts_success THEN
4368 
4369             aso_order_feedback_pub.get_exception (
4370                p_api_version=> 1.0,
4371                x_return_status=> l_return_status,
4372                x_msg_count=> l_msg_count,
4373                x_msg_data=> l_msg_data,
4374                p_app_short_name=> 'OZF', -- need to be resolved , wether it is AMS or OZF
4375                p_dequeue_mode  => DBMS_AQ.REMOVE_NODATA,
4376                p_navigation   => DBMS_AQ.FIRST_MESSAGE,
4377                x_no_more_messages=> l_no_more_messages,
4378                x_header_rec=> l_header_rec,
4379                x_old_header_rec=> l_old_header_rec,
4380                x_header_adj_tbl=> l_header_adj_tbl,
4381                x_old_header_adj_tbl=> l_old_header_adj_tbl,
4382                x_header_price_att_tbl=> l_header_price_att_tbl,
4383                x_old_header_price_att_tbl=> l_old_header_price_att_tbl,
4384                x_header_adj_att_tbl=> l_header_adj_att_tbl,
4385                x_old_header_adj_att_tbl=> l_old_header_adj_att_tbl,
4386                x_header_adj_assoc_tbl=> l_header_adj_assoc_tbl,
4387                x_old_header_adj_assoc_tbl=> l_old_header_adj_assoc_tbl,
4388                x_header_scredit_tbl=> l_header_scredit_tbl,
4389                x_old_header_scredit_tbl=> l_old_header_scredit_tbl,
4390                x_line_tbl=> l_line_tbl,
4391                x_old_line_tbl=> l_old_line_tbl,
4392                x_line_adj_tbl=> l_line_adj_tbl,
4393                x_old_line_adj_tbl=> l_old_line_adj_tbl,
4394                x_line_price_att_tbl=> l_line_price_att_tbl,
4395                x_old_line_price_att_tbl=> l_old_line_price_att_tbl,
4396                x_line_adj_att_tbl=> l_line_adj_att_tbl,
4397                x_old_line_adj_att_tbl=> l_old_line_adj_att_tbl,
4398                x_line_adj_assoc_tbl=> l_line_adj_assoc_tbl,
4399                x_old_line_adj_assoc_tbl=> l_old_line_adj_assoc_tbl,
4400                x_line_scredit_tbl=> l_line_scredit_tbl,
4401                x_old_line_scredit_tbl=> l_old_line_scredit_tbl,
4402                x_lot_serial_tbl=> l_lot_serial_tbl,
4403                x_old_lot_serial_tbl=> l_old_lot_serial_tbl,
4404                x_action_request_tbl=> l_action_request_tbl
4405             );
4406 
4407             l_navigation := DBMS_AQ.FIRST_MESSAGE ;
4408             COMMIT;
4409             x_retcode                  := 0;
4410          ELSE
4411             ozf_utility_pvt.write_conc_log;
4412             FND_MSG_PUB.INITIALIZE;
4413          END IF;
4414          EXCEPTION
4415          WHEN FND_API.G_EXC_ERROR THEN
4416             ROLLBACK TO get_excep_loop_savepoint;
4417             ozf_utility_pvt.write_conc_log('FALIED');
4418             ozf_utility_pvt.write_conc_log;
4419 
4420         WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
4421             ROLLBACK TO get_excep_loop_savepoint;
4422             ozf_utility_pvt.write_conc_log('FALIED');
4423             ozf_utility_pvt.write_conc_log;
4424 
4425         WHEN OTHERS THEN
4426             ROLLBACK TO get_excep_loop_savepoint;
4427             ozf_utility_pvt.write_conc_log('FAILED');
4428             IF FND_MSG_PUB.Check_Msg_level (FND_MSG_PUB.G_MSG_LVL_DEBUG_LOW) THEN
4429                FND_MESSAGE.Set_Name('OZF','OZF_API_DEBUG_MESSAGE');
4430                FND_MESSAGE.Set_Token('TEXT',sqlerrm);
4431                FND_MSG_PUB.Add;
4432             END IF;
4433             ozf_utility_pvt.write_conc_log;
4434          END;
4435       END LOOP exception_loop;
4436    EXCEPTION
4437       WHEN fnd_api.g_exc_error THEN
4438          x_retcode                  := 1;
4439       WHEN fnd_api.g_exc_unexpected_error THEN
4440          x_retcode                  := 1;
4441       WHEN OTHERS THEN
4442          x_retcode                  := 1;
4443    END get_exception_message;
4444 
4445 
4446    PROCEDURE reprocess_failed_gl_posting (x_errbuf  OUT NOCOPY VARCHAR2,
4447                                           x_retcode OUT NOCOPY NUMBER);
4448    PROCEDURE post_offinvoice_to_gl(x_errbuf  OUT NOCOPY VARCHAR2,
4449                                    x_retcode OUT NOCOPY NUMBER);
4450 
4451 ------------------------------------------------------------------------------
4452 -- Procedure Name
4453 --   Accrue_offers
4454 -- Purpose
4455 --   This procedure performs accruals for all offers for the folow
4456 --   1) Order Managemnt Accruals
4457 --   2) Backdating Adjustment
4458 --   3) Volume Offer Backdating
4459 --   4) reprocess all utilizations whose postings to GL have failed
4460 -- History
4461 --   7/22/2002  mpande Created
4462 --   03/19/2003 yzhao  added parameter p_run_unposted_gl to post unposted accruals to GL
4463 --                       'N' do not process failed GL postings  -- DEFAULT
4464 --                       'Y' reprocess all failed GL postings
4465 ------------------------------------------------------------------------------
4466    PROCEDURE Accrue_offers (x_errbuf OUT NOCOPY VARCHAR2,
4467                             x_retcode OUT NOCOPY NUMBER,
4468                             p_run_exception IN VARCHAR2 := 'N',
4469                             p_run_backdated_adjustment IN VARCHAR2 := 'N',
4470                             p_run_volume_off_adjustment IN VARCHAR2 := 'N',
4471                             p_run_unposted_gl IN VARCHAR2 := 'N',
4472                             p_debug IN VARCHAR2    := 'N' )    IS
4473    BEGIN
4474      g_debug_flag := p_debug;
4475 
4476      ozf_utility_pvt.write_conc_log (' <===> ORDER MANAGEMENT ACCRUALS BEGIN  <===>');
4477 
4478      ozf_utility_pvt.write_conc_log ('<====ORDER MANAGEMENT ACCRUALS BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4479 
4480      get_message( x_errbuf,
4481                   x_retcode,
4482                   p_run_exception,
4483                   p_debug );
4484 
4485      ozf_utility_pvt.write_conc_log ('<====ORDER MANAGEMENT ACCRUALS END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4486 
4487      ozf_utility_pvt.write_conc_log (' x_retcode '||x_retcode||'x_errbuf'||x_errbuf);
4488 
4489      ozf_utility_pvt.write_conc_log ('<===> ORDER MANAGEMENT ACCRUALS END  <===>');
4490 
4491      IF p_run_backdated_adjustment = 'Y' OR p_run_volume_off_adjustment = 'Y' THEN
4492         ozf_utility_pvt.write_conc_log ('<===> BACKDATED ADJUSTMENT BEGIN  <===>');
4493         ozf_utility_pvt.write_conc_log ('<====BACKDATED ADJUSTMENT BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4494 
4495      -- start backdated Adjustment only
4496         ozf_adjustment_ext_pvt.adjust_backdated_offer(
4497                          x_errbuf,
4498                          x_retcode,
4499                          p_debug );
4500         ozf_utility_pvt.write_conc_log ('<====BACKDATED ADJUSTMENT END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4501 
4502         ozf_utility_pvt.write_conc_log (' BACKDATE ADJUSTMENT x_retcode '||x_retcode||'x_errbuf'||x_errbuf);
4503 
4504         ozf_utility_pvt.write_conc_log ('<===> BACKDATED ADJUSTMENT END <===> ');
4505 
4506      END IF;
4507 
4508      ozf_utility_pvt.write_conc_log ('<===> POST OFFINVOICE UTILIZATION TO GL BEGIN  <===>');
4509      ozf_utility_pvt.write_conc_log ('<====POST OFFINVOICE UTILIZATION TO GL BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4510 
4511      post_offinvoice_to_gl(x_errbuf, x_retcode);
4512 
4513      ozf_utility_pvt.write_conc_log ('<====POST OFFINVOICE UTILIZATION TO GL END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4514      ozf_utility_pvt.write_conc_log ('<===> POST OFFINVOICE UTILIZATION TO GL END  <===>');
4515 
4516      IF p_run_volume_off_adjustment = 'Y' THEN
4517         ozf_utility_pvt.write_conc_log ('<===> VOLUME OFFER ADJUSTMENT BEGIN <=== >');
4518         ozf_utility_pvt.write_conc_log ('<====VOLUME OFFER ADJUSTMENT BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4519 
4520         ozf_adjustment_ext_pvt.adjust_volume_offer(
4521                          x_errbuf,
4522                          x_retcode,
4523                          p_debug);
4524        ozf_utility_pvt.write_conc_log ('<====VOLUME OFFER ADJUSTMENT END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4525        ozf_utility_pvt.write_conc_log (' x_retcode '||x_retcode||'x_errbuf'||x_errbuf);
4526 
4527         ozf_utility_pvt.write_conc_log ('<===> VOLUME OFFER ADJUSTMENT END  <===>');
4528      END IF;
4529 
4530      IF p_run_unposted_gl = 'Y' THEN
4531         ozf_utility_pvt.write_conc_log ('<===> REPROCESS ALL FAILED GL POSTING BEGIN <=== >');
4532         ozf_utility_pvt.write_conc_log ('<====REPROCESS ALL FAILED GL POSTING BEGIN TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4533 
4534         reprocess_failed_gl_posting(
4535                          x_errbuf,
4536                          x_retcode);
4537         ozf_utility_pvt.write_conc_log ('<====REPROCESS ALL FAILED GL POSTING END TIME '||to_char( SYSDATE ,'DD/MM/RR HH:MI:SS A.M. ')||' ====>');
4538 
4539         ozf_utility_pvt.write_conc_log (' REPROCESS_FAILED_GL_POSTING x_retcode='||x_retcode||' x_errbuf='||x_errbuf);
4540         ozf_utility_pvt.write_conc_log ('<===> REPROCESS ALL FAILED GL POSTING END  <===>');
4541 
4542      END IF;
4543 
4544 
4545    END Accrue_offers;
4546 
4547 
4548 ------------------------------------------------------------------------------
4549 -- Procedure Name
4550 --   post_accrual_to_gl
4551 -- Purpose
4552 --   This procedure posts accrual to GL
4553 -- History
4554 --   03/19/2003  Ying Zhao Created
4555 ------------------------------------------------------------------------------
4556    PROCEDURE post_accrual_to_gl(
4557       p_util_utilization_id         IN              NUMBER,
4558       p_util_object_version_number  IN              NUMBER,
4559       p_util_amount                 IN              NUMBER,
4560       p_util_plan_type              IN              VARCHAR2,
4561       p_util_plan_id                IN              NUMBER,
4562       p_util_plan_amount            IN              NUMBER,
4563       p_util_utilization_type       IN              VARCHAR2,
4564       p_util_fund_id                IN              NUMBER,
4565       p_util_acctd_amount           IN              NUMBER,
4566       p_adjust_paid_flag            IN              BOOLEAN  := false,
4567       p_util_org_id                 IN              NUMBER := NULL,
4568       x_gl_posted_flag              OUT NOCOPY      VARCHAR2,
4569       x_return_status               OUT NOCOPY      VARCHAR2,
4570       x_msg_count                   OUT NOCOPY      NUMBER,
4571       x_msg_data                    OUT NOCOPY      VARCHAR2
4572      )
4573    IS
4574      l_gl_posted_flag               VARCHAR2(1) := G_GL_FLAG_NO;
4575      l_event_id                     NUMBER;
4576      l_return_status                VARCHAR2(1);
4577      l_tmp_number                   NUMBER;
4578      l_acctd_amt                    NUMBER;
4579      l_paid_amt                     NUMBER;
4580      l_rollup_paid_amt              NUMBER;
4581      l_new_univ_amt                 NUMBER;
4582      l_currency_code                VARCHAR2(30);
4583      -- l_mc_col_8                     NUMBER;
4584      l_parent_fund_id               NUMBER;
4585      -- l_mc_record_id                 NUMBER;
4586      l_obj_num                      NUMBER;
4587      l_rate                         NUMBER;
4588      l_objfundsum_rec               ozf_objfundsum_pvt.objfundsum_rec_type := NULL;
4589      l_event_type_code              VARCHAR2(30);
4590      l_adjustment_type              VARCHAR2(1);
4591      l_orig_amt                     NUMBER;
4592      l_rollup_orig_amt              NUMBER;
4593      l_off_invoice_gl_post_flag    VARCHAR2(1);
4594      l_earned_amt  NUMBER;
4595      l_rollup_earned_amt  NUMBER;
4596      l_liability_flag     VARCHAR2(1);
4597      l_accrual_basis   VARCHAR2(30);
4598      l_exchange_rate_type          VARCHAR2(30) := FND_API.G_MISS_CHAR; --nirprasa
4599 
4600       --nirprasa, added for bug 7030415.
4601      CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
4602         SELECT exchange_rate_type
4603         FROM   ozf_sys_parameters_all
4604         WHERE  org_id = p_org_id;
4605 
4606      CURSOR c_get_fund (p_fund_id IN NUMBER) IS
4607        SELECT  object_version_number, parent_fund_id, currency_code_tc,liability_flag,accrual_basis
4608        FROM    ozf_funds_all_b
4609        WHERE   fund_id = p_fund_id;
4610 
4611      /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
4612      CURSOR c_mc_trans(p_fund_id IN NUMBER) IS
4613          SELECT mc_record_id
4614                ,object_version_number
4615          FROM ozf_mc_transactions_all
4616          WHERE source_object_name ='FUND'
4617          AND source_object_id = p_fund_id;
4618       */
4619 
4620      CURSOR c_parent (p_fund_id IN NUMBER)IS
4621         SELECT fund_id
4622               ,object_version_number
4623         FROM ozf_funds_all_b
4624         connect by prior  parent_fund_id =fund_id
4625         start with fund_id =  p_fund_id;
4626 
4627      -- rimehrot: for R12 update ozf_object_fund_summary table
4628      CURSOR c_get_objfundsum_rec(p_object_type IN VARCHAR2, p_object_id IN NUMBER, p_fund_id IN NUMBER) IS
4629          SELECT objfundsum_id
4630               , object_version_number
4631               , earned_amt
4632               , paid_amt
4633               , plan_curr_earned_amt
4634               , plan_curr_paid_amt
4635               , univ_curr_earned_amt
4636               , univ_curr_paid_amt
4637         FROM   ozf_object_fund_summary
4638         WHERE  object_type = p_object_type
4639         AND    object_id = p_object_id
4640         AND    fund_id = p_fund_id;
4641 
4642       CURSOR c_offinv_flag(p_org_id IN NUMBER) IS
4643         SELECT  NVL(sob.gl_acct_for_offinv_flag, 'F')
4644         FROM    ozf_sys_parameters_all sob
4645         WHERE   sob.org_id = p_org_id;
4646 
4647    BEGIN
4648      SAVEPOINT  post_accrual_to_gl_sp;
4649 
4650       IF g_debug_flag = 'Y' THEN
4651          ozf_utility_pvt.write_conc_log ('    D: post_accrual_to_gl() BEGIN posting to GL for utilization id ' ||
4652                      p_util_utilization_id ||
4653                      ' object_version_number=' || p_util_object_version_number ||
4654                      ' amount=' || p_util_amount ||
4655                      ' plan_type=' || p_util_plan_type ||
4656                      ' utilization_type=' || p_util_utilization_type ||
4657                      ' util_fund_id=' || p_util_fund_id ||
4658                      ' acctd_amount=' || p_util_acctd_amount
4659                      );
4660       END IF;
4661 
4662      IF p_util_plan_type IN ( 'OFFR' , 'PRIC')  THEN         -- yzhao: 10/20/2003 PRICE_LIST is changed to PRIC
4663         -- moved from  IF  l_gl_posted_flag IN(G_GL_FLAG_YES,G_GL_FLAG_NULL,G_GL_FLAG_NOLIAB) THEN
4664         -- to fix bug 5128552
4665         OPEN c_get_fund(p_util_fund_id);
4666         FETCH c_get_fund INTO l_obj_num, l_parent_fund_id, l_currency_code, l_liability_flag,l_accrual_basis;
4667         CLOSE c_get_fund;
4668 
4669         -- yzhao: 11/25/2003 11.5.10 post gl for off invoice discount
4670         IF p_util_utilization_type IN ('ACCRUAL', 'LEAD_ACCRUAL', 'ADJUSTMENT', 'LEAD_ADJUSTMENT', 'UTILIZED','SALES_ACCRUAL') THEN
4671            IF  p_util_utilization_type IN ('ACCRUAL', 'LEAD_ACCRUAL') THEN
4672               l_event_type_code := 'ACCRUAL';
4673               IF l_accrual_basis = 'CUSTOMER' AND NVL(l_liability_flag,'N')= 'N' THEN
4674                  l_gl_posted_flag := G_GL_FLAG_NOLIAB;
4675               END IF;
4676            ELSIF p_util_utilization_type = 'UTILIZED' THEN
4677               OPEN c_offinv_flag(p_util_org_id);
4678               FETCH c_offinv_flag INTO l_off_invoice_gl_post_flag;
4679               CLOSE c_offinv_flag;
4680 
4681               IF l_off_invoice_gl_post_flag = 'F' THEN
4682                  l_gl_posted_flag := G_GL_FLAG_NULL;
4683               ELSE
4684                  l_event_type_code := 'OFF_INVOICE';
4685               END IF;
4686            ELSIF p_util_utilization_type = 'SALES_ACCRUAL' THEN
4687               l_gl_posted_flag := G_GL_FLAG_NOLIAB;
4688            ELSE  -- 'ADJUSTMENT', 'LEAD_ADJUSTMENT'
4689               l_event_type_code   := 'ACCRUAL_ADJUSTMENT';
4690            END IF;
4691 
4692            IF NVL(p_util_amount,0) >= 0 THEN
4693               l_adjustment_type   := 'P'; -- positive
4694            ELSE
4695               l_adjustment_type   := 'N'; -- negetive adjustment
4696            END IF;
4697 
4698 
4699           IF  l_gl_posted_flag = G_GL_FLAG_NO THEN
4700              OZF_GL_INTERFACE_PVT.Post_Accrual_To_GL (
4701                 p_api_version       => 1.0
4702               , p_init_msg_list     => fnd_api.g_false
4703               , p_commit            => fnd_api.g_false
4704               , p_validation_level  => fnd_api.g_valid_level_full
4705 
4706                ,p_utilization_id    =>  p_util_utilization_id
4707                ,p_utilization_type  => l_event_type_code
4708                ,p_adjustment_type   => l_adjustment_type
4709 
4710               , x_return_status     => l_return_status
4711               , x_msg_data          => x_msg_data
4712               , x_msg_count         => x_msg_count
4713               , x_event_id          => l_event_id
4714              );
4715 
4716              IF g_debug_flag = 'Y' THEN
4717                 ozf_utility_pvt.write_conc_log ('   D: post_accrual_to_gl() create_gl_entry for utilization id '
4718                                    || p_util_utilization_id || ' returns ' || l_return_status);
4719              END IF;
4720 
4721              IF l_return_status = fnd_api.g_ret_sts_success THEN
4722                 l_gl_posted_flag := G_GL_FLAG_YES;  -- 'Y';
4723              ELSE
4724               -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
4725                 l_gl_posted_flag := G_GL_FLAG_FAIL;  -- 'F';
4726               -- 07/17/2003 yzhao: log error message
4727                 fnd_msg_pub.count_and_get (
4728                     p_count    => x_msg_count,
4729                     p_data     => x_msg_data,
4730                     p_encoded  => fnd_api.g_false
4731                  );
4732                 ozf_utility_pvt.write_conc_log('   /****** Failed to post to GL ******/ for utilization id ' || p_util_utilization_id);
4733 
4734                 ozf_utility_pvt.write_conc_log;
4735                 fnd_msg_pub.initialize;
4736               END IF;
4737 
4738            END IF; --l_gl_posted_flag = G_GL_FLAG_NO
4739 
4740            -- update utilization gl_posted_flag directly to avoid all validations
4741            UPDATE ozf_funds_utilized_all_b
4742            SET last_update_date = SYSDATE
4743                 , last_updated_by = NVL (fnd_global.user_id, -1)
4744                 , last_update_login = NVL (fnd_global.conc_login_id, -1)
4745                 , object_version_number = p_util_object_version_number + 1
4746                 , gl_posted_flag = l_gl_posted_flag
4747                 --, gl_date = sysdate
4748             WHERE utilization_id = p_util_utilization_id
4749             AND   object_version_number = p_util_object_version_number;
4750 
4751             IF  l_gl_posted_flag IN(G_GL_FLAG_YES,G_GL_FLAG_NULL,G_GL_FLAG_NOLIAB) THEN
4752 
4753               IF g_universal_currency IS NULL THEN
4754                  IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error) THEN
4755                     fnd_message.set_name('OZF', 'OZF_UNIV_CURR_NOT_FOUND');
4756                      fnd_msg_pub.add;
4757                   END IF;
4758                   RAISE fnd_api.g_exc_error;
4759               END IF;
4760 
4761               --Added for bug 7030415
4762                 OPEN c_get_conversion_type(p_util_org_id);
4763                 FETCH c_get_conversion_type INTO l_exchange_rate_type;
4764                 CLOSE c_get_conversion_type;
4765 
4766                 IF g_debug_flag = 'Y' THEN
4767                         ozf_utility_pvt.write_conc_log('**************************START****************************');
4768                         ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' From Amount p_util_amount: '||p_util_amount );
4769                         ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' From Curr l_currency_code: '||l_currency_code );
4770                         ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' To Curr g_universal_currency: '|| g_universal_currency);
4771                         --ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' l_exchange_rate_type: '|| l_exchange_rate_type);
4772                 END IF;
4773 
4774               ozf_utility_pvt.convert_currency(
4775                     x_return_status => l_return_status
4776                     ,p_from_currency => l_currency_code
4777                     ,p_to_currency => g_universal_currency
4778                     ,p_conv_type   => l_exchange_rate_type
4779                     ,p_from_amount => p_util_amount
4780                     ,x_to_amount => l_new_univ_amt
4781                     ,x_rate => l_rate);
4782 
4783               IF g_debug_flag = 'Y' THEN
4784                 ozf_utility_pvt.write_conc_log('post_accrual_to_gl' ||' Converted Amount l_new_univ_amt: '|| l_new_univ_amt);
4785                 ozf_utility_pvt.write_conc_log('Utilization amount is converted from fund curr to universal curr');
4786                 ozf_utility_pvt.write_conc_log('***************************END******************************');
4787               END IF;
4788 
4789               IF l_return_status = fnd_api.g_ret_sts_error THEN
4790                  RAISE fnd_api.g_exc_error;
4791               ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
4792                  RAISE fnd_api.g_exc_unexpected_error;
4793               END IF;
4794 
4795               IF l_gl_posted_flag = G_GL_FLAG_NOLIAB THEN
4796                  l_orig_amt := p_util_amount;
4797                  l_rollup_orig_amt := l_new_univ_amt;
4798               ELSE
4799                 -- rimehrot changed for R12, Populate new table ozf_object_fund_summary
4800                  l_objfundsum_rec := NULL;
4801                  OPEN c_get_objfundsum_rec(p_util_plan_type
4802                                      , p_util_plan_id
4803                                      , p_util_fund_id);
4804                  FETCH c_get_objfundsum_rec INTO l_objfundsum_rec.objfundsum_id
4805                                            , l_objfundsum_rec.object_version_number
4806                                            , l_objfundsum_rec.earned_amt
4807                                            , l_objfundsum_rec.paid_amt
4808                                            , l_objfundsum_rec.plan_curr_earned_amt
4809                                            , l_objfundsum_rec.plan_curr_paid_amt
4810                                            , l_objfundsum_rec.univ_curr_earned_amt
4811                                            , l_objfundsum_rec.univ_curr_paid_amt;
4812                  CLOSE c_get_objfundsum_rec;
4813 
4814               -- yzhao: 11/25/2003  11.5.10 need to update budget earned amount for accrual, earned and paid amount for off-invoice discount
4815                  IF p_util_utilization_type = 'UTILIZED' OR p_adjust_paid_flag THEN
4816                     l_paid_amt := p_util_amount;
4817                     l_rollup_paid_amt := l_new_univ_amt;
4818                    -- l_mc_col_8 := l_acctd_amt;
4819 
4820                     l_objfundsum_rec.paid_amt := NVL(l_objfundsum_rec.paid_amt, 0) + NVL(l_paid_amt, 0);
4821                     l_objfundsum_rec.plan_curr_paid_amt := NVL(l_objfundsum_rec.plan_curr_paid_amt, 0)
4822                                                                   + NVL(p_util_plan_amount, 0);
4823                     l_objfundsum_rec.univ_curr_paid_amt := NVL(l_objfundsum_rec.univ_curr_paid_amt, 0)
4824                                                                   + NVL(l_rollup_paid_amt, 0);
4825                  END IF;
4826 
4827                  l_earned_amt := p_util_amount;
4828                  l_rollup_earned_amt := l_new_univ_amt;
4829 
4830               -- rimehrot: for R12, populate paid/earned columns in ozf_object_fund_summary
4831                  l_objfundsum_rec.earned_amt := NVL(l_objfundsum_rec.earned_amt, 0) + NVL(p_util_amount, 0);
4832                  l_objfundsum_rec.plan_curr_earned_amt := NVL(l_objfundsum_rec.plan_curr_earned_amt, 0)
4833                                                               + NVL(p_util_plan_amount, 0);
4834                  l_objfundsum_rec.univ_curr_earned_amt := NVL(l_objfundsum_rec.univ_curr_earned_amt, 0)
4835                                                               + NVL(l_new_univ_amt, 0);
4836                  --rimehrot, for R12
4837                  ozf_objfundsum_pvt.update_objfundsum(
4838                        p_api_version                => 1.0,
4839                        p_init_msg_list              => Fnd_Api.G_FALSE,
4840                        p_validation_level           => Fnd_Api.G_VALID_LEVEL_NONE,
4841                        p_objfundsum_rec             => l_objfundsum_rec,
4842                        x_return_status              => l_return_status,
4843                        x_msg_count                  => x_msg_count,
4844                        x_msg_data                   => x_msg_data
4845                     );
4846                  IF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
4847                    RAISE fnd_api.g_exc_unexpected_error;
4848                  ELSIF l_return_status = fnd_api.g_ret_sts_error THEN
4849                    RAISE fnd_api.g_exc_error;
4850                  END IF;
4851               -- end R12 changes
4852 
4853               END IF; -- p_util_utilization_type = 'SALES_ACCRUAL'
4854 
4855               UPDATE ozf_funds_all_b
4856               SET    original_budget = NVL(original_budget, 0) + NVL(l_orig_amt, 0)
4857                     ,rollup_original_budget = NVL(rollup_original_budget, 0) + NVL(l_rollup_orig_amt, 0)
4858                     ,earned_amt = NVL(earned_amt, 0) + NVL(l_earned_amt, 0)
4859                     ,paid_amt = NVL(paid_amt, 0 ) + NVL(l_paid_amt, 0)
4860                     ,rollup_earned_amt = NVL(rollup_earned_amt, 0) +  NVL(l_rollup_earned_amt, 0)
4861                     ,rollup_paid_amt = NVL(rollup_paid_amt, 0) + NVL(l_rollup_paid_amt, 0)
4862                     ,object_version_number = l_obj_num + 1
4863               WHERE fund_id =  p_util_fund_id
4864               AND   object_version_number = l_obj_num;
4865 
4866               IF l_parent_fund_id is NOT NULL THEN
4867                  FOR fund IN c_parent(l_parent_fund_id)
4868                  LOOP
4869                       UPDATE ozf_funds_all_b
4870                       SET object_version_number = fund.object_version_number + 1
4871                          ,rollup_earned_amt = NVL(rollup_earned_amt,0) + NVL(l_new_univ_amt,0)
4872                          ,rollup_paid_amt = NVL(rollup_paid_amt,0) + NVL(l_rollup_paid_amt,0)
4873                          ,rollup_original_budget = NVL(rollup_original_budget,0) + NVL(l_rollup_orig_amt,0)
4874                       WHERE fund_id = fund.fund_id
4875                       AND object_version_number = fund.object_version_number;
4876                  END LOOP;
4877               END IF;
4878 
4879 
4880               /* R12: yzhao bug 4669269 - obsolete ozf_mc_transactions
4881               OPEN c_mc_trans(p_util_fund_id);
4882               FETCH c_mc_trans INTO l_mc_record_id, l_obj_num;
4883               CLOSE c_mc_trans;
4884 
4885               -- update ozf_mc_transaction_all table.
4886               UPDATE ozf_mc_transactions_all
4887                 SET amount_column7 = NVL(amount_column7, 0) + NVL(p_util_acctd_amount,0),
4888                     amount_column8 = NVL(amount_column8, 0) + NVL(l_mc_col_8, 0),
4889                     object_version_number = l_obj_num + 1
4890                 WHERE mc_record_id = l_mc_record_id
4891                 AND object_version_number = l_obj_num;
4892                */
4893           END IF; -- l_gl_posted_flag
4894         END IF; -- for utilization_type
4895      END IF; -- end of plan_type
4896 
4897 
4898      x_gl_posted_flag := l_gl_posted_flag;
4899      x_return_status := fnd_api.g_ret_sts_success;
4900 
4901      IF g_debug_flag = 'Y' THEN
4902         ozf_utility_pvt.write_conc_log ('    D: post_accrual_to_gl() ENDs for utilization id ' || p_util_utilization_id
4903          || ' final gl_posted_flag=' || x_gl_posted_flag);
4904      END IF;
4905 
4906    EXCEPTION
4907      WHEN OTHERS THEN
4908        ROLLBACK TO post_accrual_to_gl_sp;
4909        ozf_utility_pvt.write_conc_log('    D: post_accrual_to_gl(): exception ');
4910        x_return_status            := fnd_api.g_ret_sts_unexp_error;
4911        fnd_msg_pub.count_and_get (
4912             p_count    => x_msg_count,
4913             p_data     => x_msg_data,
4914             p_encoded  => fnd_api.g_false
4915        );
4916    END post_accrual_to_gl;
4917 
4918 
4919 
4920 ------------------------------------------------------------------------------
4921 -- Procedure Name
4922 --   reprocess_failed_gl_posting
4923 -- Purpose
4924 --   This procedure repost to GL for all failed gl postings
4925 -- History
4926 --   03-20-00  yzhao   Created
4927 ------------------------------------------------------------------------------
4928    PROCEDURE reprocess_failed_gl_posting (x_errbuf  OUT NOCOPY VARCHAR2,
4929                                           x_retcode OUT NOCOPY NUMBER
4930                                          ) IS
4931      l_gl_posted_flag          VARCHAR2 (1);
4932      l_return_status           VARCHAR2 (1);
4933      l_msg_count               NUMBER;
4934      l_msg_data                VARCHAR2(2000);
4935 
4936      l_utilIdTbl               utilIdTbl;
4937      l_objVerTbl               objVerTbl;
4938      l_amountTbl               amountTbl;
4939      l_planTypeTbl             planTypeTbl;
4940      l_planIdTbl               planIdTbl;
4941      l_planAmtTbl              planAmtTbl;
4942      l_utilTypeTbl             utilTypeTbl;
4943      l_fundIdTbl               fundIdTbl;
4944      l_acctAmtTbl              acctAmtTbl;
4945      l_orgIdTbl                orgIdTbl;
4946 
4947      CURSOR c_get_failed_gl_posting IS
4948        SELECT utilization_id, object_version_number,
4949               plan_type, utilization_type,
4950               amount, fund_id, acctd_amount, plan_curr_amount, plan_id,org_id
4951        FROM   ozf_funds_utilized_all_b
4952        WHERE  plan_type IN ( 'OFFR' , 'PRIC')       -- yzhao: 10/20/2003 PRICE_LIST is changed to PRIC
4953          -- AND  utilization_type = 'ACCRUAL'          yzhao: 01/29/2004 11.5.10 off-invoice offer, LEAD_ACCRUAL may post to GL too
4954          AND  gl_posted_flag = G_GL_FLAG_FAIL;  -- 'F';
4955 
4956    BEGIN
4957       IF g_debug_flag = 'Y' THEN
4958          ozf_utility_pvt.write_conc_log ('    D: Begin posting to GL for all failed postings');
4959       END IF;
4960 
4961      OPEN c_get_failed_gl_posting;
4962      LOOP
4963          FETCH c_get_failed_gl_posting BULK COLLECT INTO l_utilIdTbl, l_objVerTbl
4964                                                        , l_planTypeTbl, l_utilTypeTbl
4965                                                        , l_amountTbl, l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
4966                                                        LIMIT g_bulk_limit;
4967          FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
4968              post_accrual_to_gl( p_util_utilization_id        => l_utilIdTbl(i)
4969                                , p_util_object_version_number => l_objVerTbl(i)
4970                                , p_util_amount                => l_amountTbl(i)
4971                                , p_util_plan_type             => l_planTypeTbl(i)
4972                                , p_util_plan_id               => l_planIdTbl(i)
4973                                , p_util_plan_amount           => l_planAmtTbl(i)
4974                                , p_util_utilization_type      => l_utilTypeTbl(i)
4975                                , p_util_fund_id               => l_fundIdTbl(i)
4976                                , p_util_acctd_amount          => l_acctAmtTbl(i)
4977                                , p_util_org_id                     => l_orgIdTbl(i)
4978                                , x_gl_posted_flag             => l_gl_posted_flag
4979                                , x_return_status              => l_return_status
4980                                , x_msg_count                  => l_msg_count
4981                                , x_msg_data                   => l_msg_data
4982                            );
4983 
4984              IF l_return_status <> fnd_api.g_ret_sts_success THEN
4985                 -- failed again. Leave as it is.
4986                 ozf_utility_pvt.write_conc_log('   /****** Failed to post to GL ******/ for utilization id ' || l_utilIdTbl(i));
4987              ELSE
4988                 IF g_debug_flag = 'Y' THEN
4989                    ozf_utility_pvt.write_conc_log ('    D: successfully posted to GL for utilization id ' || l_utilIdTbl(i)
4990                                 || '  x_gl_posted_flag=' || l_gl_posted_flag);
4991                 END IF;
4992 
4993                 -- yzhao: 03/04/2004 post gl for related accruals from offer adjustment or object reconcile
4994                 IF l_gl_posted_flag = G_GL_FLAG_YES THEN
4995                     post_related_accrual_to_gl(
4996                         p_utilization_id              => l_utilIdTbl(i)
4997                       , p_utilization_type            => l_utilTypeTbl(i)
4998                       , x_return_status               => l_return_status
4999                       , x_msg_count                   => l_msg_count
5000                       , x_msg_data                    => l_msg_data
5001                   );
5002                 END IF;
5003 
5004              END IF;
5005          END LOOP;  -- FOR i IN NVL(p_utilIdTbl.FIRST, 1) .. NVL(p_utilIdTbl.LAST, 0) LOOP
5006 
5007          EXIT WHEN c_get_failed_gl_posting%NOTFOUND;
5008      END LOOP;  -- bulk fetch loop
5009      CLOSE c_get_failed_gl_posting;
5010 
5011      x_retcode := 0;
5012      IF g_debug_flag = 'Y' THEN
5013         ozf_utility_pvt.write_conc_log ('    D: End successfully posting to GL for all failed postings');
5014      END IF;
5015 
5016    EXCEPTION
5017      WHEN OTHERS THEN
5018        x_retcode                  := 1;
5019        ozf_utility_pvt.write_conc_log('   /****** Failed to post to GL - exception ' ||  sqlcode || ' ******/' );
5020    END reprocess_failed_gl_posting;
5021 
5022 
5023 ------------------------------------------------------------------------------
5024 -- Procedure Name
5025 --   post_offinvoice_to_gl
5026 -- Purpose
5027 --   This procedure posts utilization created by off-invoice offer to GL only when AutoInvoice workflow is done
5028 -- History
5029 --   03/19/2003  Ying Zhao Created
5030 ------------------------------------------------------------------------------
5031   PROCEDURE post_offinvoice_to_gl(
5032              x_errbuf  OUT NOCOPY VARCHAR2,
5033              x_retcode OUT NOCOPY NUMBER     )
5034    IS
5035      l_gl_posted_flag             VARCHAR2(1);
5036      l_invoice_line_id            NUMBER;
5037      l_gl_date                    DATE;
5038      l_return_status              VARCHAR2 (1);
5039      l_msg_count                  NUMBER;
5040      l_msg_data                   VARCHAR2 (2000);
5041      l_order_number               NUMBER;
5042      l_object_id                  NUMBER := 0;
5043 
5044      l_utilIdTbl               utilIdTbl;
5045      l_objVerTbl               objVerTbl;
5046      l_amountTbl               amountTbl;
5047      l_planTypeTbl             planTypeTbl;
5048      l_planIdTbl               planIdTbl;
5049      l_planAmtTbl              planAmtTbl;
5050      l_utilTypeTbl             utilTypeTbl;
5051      l_fundIdTbl               fundIdTbl;
5052      l_acctAmtTbl              acctAmtTbl;
5053      l_orgIdTbl                orgIdTbl;
5054      l_objectIdTbl             objectIdTbl;
5055      l_priceAdjTbl             priceAdjTbl;
5056 
5057      -- yzhao: 03/21/2003 get invoiced order's utilization record, post to GL
5058      CURSOR c_get_all_util_rec IS
5059        SELECT utilization_id, object_version_number,
5060               plan_type, utilization_type,
5061               amount, fund_id, acctd_amount, plan_curr_amount, plan_id
5062               ,org_id,object_id, price_adjustment_id
5063        FROM   ozf_funds_utilized_all_b
5064        WHERE  utilization_type = 'UTILIZED'
5065        AND    gl_posted_flag = G_GL_FLAG_NO    -- 'N'
5066        AND    object_type = 'ORDER'
5067        AND    price_adjustment_id IS NOT NULL;
5068 
5069      CURSOR c_get_invoice_status(p_price_adjustment_id IN NUMBER, p_order_number IN  VARCHAR2) IS
5070        SELECT customer_trx_line_id, cust.trx_date
5071        FROM   ra_customer_trx_all cust
5072             , ra_customer_trx_lines_all cust_lines
5073             , oe_price_adjustments price
5074        WHERE  price.price_adjustment_id = p_price_adjustment_id
5075        AND    cust_lines.customer_trx_line_id IS NOT NULL
5076        AND    interface_line_context = 'ORDER ENTRY'
5077        AND    cust_lines.interface_line_attribute6 = TO_CHAR(price.line_id)
5078        AND    cust_lines.sales_order = p_order_number -- added for partial index; performance bug fix 3917556
5079        AND    cust.customer_trx_id = cust_lines.customer_trx_id;
5080 
5081 
5082          -- added for 3917556
5083       CURSOR c_get_offer_info (p_header_id IN NUMBER) IS
5084          SELECT order_number
5085            FROM oe_order_headers_all
5086           WHERE header_id = p_header_id;
5087 
5088    BEGIN
5089      x_retcode := 0;
5090      SAVEPOINT  post_offinvoice_to_gl_sp;
5091 
5092      IF g_debug_flag = 'Y' THEN
5093         ozf_utility_pvt.write_conc_log ('    D: post_offinvoice_to_gl() BEGIN ');
5094      END IF;
5095 
5096      OPEN c_get_all_util_rec;
5097      LOOP
5098         FETCH c_get_all_util_rec BULK COLLECT INTO l_utilIdTbl, l_objVerTbl
5099                                                        , l_planTypeTbl, l_utilTypeTbl
5100                                                        , l_amountTbl, l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl,
5101                                                        l_planIdTbl,l_orgIdTbl,l_objectIdTbl,l_priceAdjTbl
5102                                                        LIMIT g_bulk_limit;
5103 
5104 
5105         IF g_debug_flag = 'Y' THEN
5106            ozf_utility_pvt.write_conc_log ('    D: l_utilIdTbl count: ' || l_utilIdTbl.COUNT);
5107         END IF;
5108 
5109         FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
5110 
5111            IF l_object_id <> l_objectIdTbl(i) THEN
5112               l_object_id := l_objectIdTbl(i);
5113               OPEN c_get_offer_info(l_object_id);
5114               FETCH c_get_offer_info INTO l_order_number;
5115               CLOSE c_get_offer_info;
5116            END IF;
5117 
5118            l_invoice_line_id := NULL; --Bugfix: 7431334
5119 
5120            OPEN c_get_invoice_status(l_priceAdjTbl(i), l_order_number);
5121            FETCH c_get_invoice_status INTO l_invoice_line_id, l_gl_date;
5122            CLOSE c_get_invoice_status;
5123 
5124            IF l_invoice_line_id IS NOT NULL THEN
5125 
5126                -- fix for bug 6998502
5127               IF l_gl_date IS NULL THEN
5128                l_gl_date := sysdate;
5129               END IF;
5130 
5131               FORALL t_i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
5132                UPDATE ozf_funds_utilized_all_b
5133                SET gl_date = l_gl_date
5134                WHERE utilization_id = l_utilIdTbl(t_i);
5135 
5136               post_accrual_to_gl( p_util_utilization_id        => l_utilIdTbl(i)
5137                                , p_util_object_version_number => l_objVerTbl(i)
5138                                , p_util_amount                => l_amountTbl(i)
5139                                , p_util_plan_type             => l_planTypeTbl(i)
5140                                , p_util_plan_id               => l_planIdTbl(i)
5141                                , p_util_plan_amount           => l_planAmtTbl(i)
5142                                , p_util_utilization_type      => 'UTILIZED'
5143                                , p_util_fund_id               => l_fundIdTbl(i)
5144                                , p_util_acctd_amount          => l_acctAmtTbl(i)
5145                                , x_gl_posted_flag             => l_gl_posted_flag
5146                                , x_return_status              => l_return_status
5147                                , x_msg_count                  => l_msg_count
5148                                , x_msg_data                   => l_msg_data
5149                            );
5150 
5151              -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
5152               IF g_debug_flag = 'Y' THEN
5153                  ozf_utility_pvt.write_conc_log ('    D:  post_offinvoice_to_gl() post_accrual_to_gl(util_id='
5154                            || l_utilIdTbl(i)
5155                            || ') returns ' || l_return_status || ' x_gl_posted_flag' || l_gl_posted_flag);
5156               END IF;
5157 
5158              -- yzhao: 03/04/2004 post gl for related accruals from offer adjustment or object reconcile
5159               IF l_return_status = fnd_api.g_ret_sts_success AND l_gl_posted_flag = G_GL_FLAG_YES THEN
5160                  post_related_accrual_to_gl(
5161                       p_utilization_id              => l_utilIdTbl(i)
5162                     , p_utilization_type            => 'UTILIZED'
5163                     , p_gl_date                     => l_gl_date
5164                     , x_return_status               => l_return_status
5165                     , x_msg_count                   => l_msg_count
5166                     , x_msg_data                    => l_msg_data
5167                 );
5168               END IF;
5169            END IF; --l_invoice_line_id IS NOT
5170 
5171         END LOOP;  -- FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
5172 
5173         EXIT WHEN c_get_all_util_rec%NOTFOUND;
5174      END LOOP;   -- bulk fetch
5175      CLOSE c_get_all_util_rec;
5176 
5177      IF g_debug_flag = 'Y' THEN
5178          ozf_utility_pvt.write_conc_log ('    D: post_offinvoice_to_gl() END');
5179      END IF;
5180 
5181 
5182    EXCEPTION
5183      WHEN OTHERS THEN
5184        ROLLBACK TO post_offinvoice_to_gl_sp;
5185        x_retcode := 1;
5186        ozf_utility_pvt.write_conc_log('    D: post_offinvoice_to_gl(): exception ');
5187        fnd_msg_pub.count_and_get (
5188             p_count    => l_msg_count,
5189             p_data     => l_msg_data,
5190             p_encoded  => fnd_api.g_false
5191        );
5192        x_errbuf := l_msg_data;
5193    END post_offinvoice_to_gl;
5194 
5195 ------------------------------------------------------------------------------
5196 -- Procedure Name
5197 --   post_related_accrual_to_gl
5198 -- Purpose
5199 --   This procedure posts utilization(from offer adjustment or offer reconcile) to GL
5200 --        called when the original utilization is posted to GL successfully
5201 -- History
5202 --   03/04/2003  Ying Zhao Created
5203 ------------------------------------------------------------------------------
5204    PROCEDURE post_related_accrual_to_gl(
5205       p_utilization_id              IN              NUMBER,
5206       p_utilization_type            IN              VARCHAR2,
5207       p_gl_date                     IN              DATE      := NULL,
5208       x_return_status               OUT NOCOPY      VARCHAR2,
5209       x_msg_count                   OUT NOCOPY      NUMBER,
5210       x_msg_data                    OUT NOCOPY      VARCHAR2)
5211    IS
5212      l_adjust_paid_flag             BOOLEAN := false;
5213      l_gl_posted_flag               VARCHAR2(1) := NULL;
5214      l_return_status                VARCHAR2 (1);
5215      l_msg_count                    NUMBER;
5216      l_msg_data                     VARCHAR2 (2000);
5217 
5218      l_utilIdTbl                    utilIdTbl;
5219      l_objVerTbl                    objVerTbl;
5220      l_amountTbl                    amountTbl;
5221      l_planTypeTbl                  planTypeTbl;
5222      l_planIdTbl                    planIdTbl;
5223      l_planAmtTbl                   planAmtTbl;
5224      l_utilTypeTbl                  utilTypeTbl;
5225      l_fundIdTbl                    fundIdTbl;
5226      l_acctAmtTbl                   acctAmtTbl;
5227      l_orgIdTbl                     orgIdTbl;
5228      -- yzhao: 03/04/2004 get related accraul records, post to GL
5229      CURSOR c_get_related_accrual IS
5230        SELECT utilization_id, object_version_number, plan_type, utilization_type, amount
5231             , fund_id, acctd_amount, plan_curr_amount, plan_id,org_id
5232        FROM   ozf_funds_utilized_all_b
5233        WHERE  (gl_posted_flag = G_GL_FLAG_NO OR gl_posted_flag = G_GL_FLAG_FAIL)
5234        AND    orig_utilization_id = p_utilization_id;
5235 
5236    BEGIN
5237      SAVEPOINT  post_related_accrual_to_gl_sp;
5238      IF g_debug_flag = 'Y' THEN
5239         ozf_utility_pvt.write_conc_log ('    D: post_related_accrual_to_gl() BEGIN posting related accruals to GL for utilization id ' || p_utilization_id);
5240      END IF;
5241 
5242      IF p_utilization_type = 'UTILIZED' THEN
5243         l_adjust_paid_flag := true;
5244      END IF;
5245 
5246      OPEN c_get_related_accrual;
5247      LOOP
5248          FETCH c_get_related_accrual BULK COLLECT
5249          INTO l_utilIdTbl, l_objVerTbl, l_planTypeTbl, l_utilTypeTbl, l_amountTbl
5250             , l_fundIdTbl, l_acctAmtTbl, l_planAmtTbl, l_planIdTbl,l_orgIdTbl
5251          LIMIT g_bulk_limit;
5252 
5253          IF p_gl_date IS NOT NULL THEN
5254              FORALL i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0)
5255                  UPDATE ozf_funds_utilized_all_b
5256                     SET gl_date = p_gl_date
5257                   WHERE utilization_id = l_utilIdTbl(i);
5258          END IF;
5259 
5260          FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
5261              post_accrual_to_gl( p_util_utilization_id        => l_utilIdTbl(i)
5262                                , p_util_object_version_number => l_objVerTbl(i)
5263                                , p_util_amount                => l_amountTbl(i)
5264                                , p_util_plan_type             => l_planTypeTbl(i)
5265                                , p_util_plan_id               => l_planIdTbl(i)
5266                                , p_util_plan_amount           => l_planAmtTbl(i)
5267                                , p_util_utilization_type      => l_utilTypeTbl(i)
5268                                , p_util_fund_id               => l_fundIdTbl(i)
5269                                , p_util_acctd_amount          => l_acctAmtTbl(i)
5270                                , p_adjust_paid_flag           => l_adjust_paid_flag
5271                                , p_util_org_id                => l_orgIdTbl(i)
5272                                , x_gl_posted_flag             => l_gl_posted_flag
5273                                , x_return_status              => l_return_status
5274                                , x_msg_count                  => l_msg_count
5275                                , x_msg_data                   => l_msg_data
5276                            );
5277 
5278             -- do not raise exception for gl posting error. Just mark it as failed and deal with it later
5279             IF g_debug_flag = 'Y' THEN
5280                ozf_utility_pvt.write_conc_log('    D:  post_related_accrual_to_gl() post_accrual_to_gl(util_id=' || l_utilIdTbl(i)
5281                            || ') returns ' || l_return_status || ' x_gl_posted_flag' || l_gl_posted_flag);
5282             END IF;
5283          END LOOP; -- FOR i IN NVL(l_utilIdTbl.FIRST, 1) .. NVL(l_utilIdTbl.LAST, 0) LOOP
5284 
5285          EXIT WHEN c_get_related_accrual%NOTFOUND;
5286      END LOOP;  -- bulk fetch
5287      CLOSE c_get_related_accrual;
5288 
5289      x_return_status := fnd_api.g_ret_sts_success;
5290      IF g_debug_flag = 'Y' THEN
5291         ozf_utility_pvt.write_conc_log ('    D: post_related_accrual_to_gl() ENDs for utilization id ' || p_utilization_id);
5292      END IF;
5293 
5294    EXCEPTION
5295      WHEN OTHERS THEN
5296        ROLLBACK TO post_related_accrual_to_gl_sp;
5297        ozf_utility_pvt.write_conc_log('    D: post_related_accrual_to_gl(): exception ');
5298        x_return_status            := fnd_api.g_ret_sts_unexp_error;
5299        fnd_msg_pub.count_and_get (
5300             p_count    => x_msg_count,
5301             p_data     => x_msg_data,
5302             p_encoded  => fnd_api.g_false
5303        );
5304 
5305    END post_related_accrual_to_gl;
5306 
5307 END ozf_accrual_engine;