DBA Data[Home] [Help]

PACKAGE BODY: APPS.OZF_FUND_ADJUSTMENT_PVT

Source


1 PACKAGE BODY OZF_FUND_ADJUSTMENT_PVT AS
2 /*$Header: ozfvadjb.pls 120.48.12020000.3 2013/01/31 07:00:26 ninarasi ship $*/
3 
4    g_pkg_name         CONSTANT VARCHAR2 (30) := 'OZF_Fund_Adjustment_PVT';
5    g_cons_fund_mode   CONSTANT VARCHAR2 (30) := 'WORKFLOW';
6    G_DEBUG BOOLEAN := FND_MSG_PUB.check_msg_level(FND_MSG_PUB.g_msg_lvl_debug_high);
7    g_recal_flag CONSTANT VARCHAR2(1)  :=  NVL(fnd_profile.value('OZF_BUDGET_ADJ_ALLOW_RECAL'),'N');
8    G_TPM_PROCESS_ENABLED VARCHAR2 (1) :=  NVL(fnd_profile.VALUE ('OZF_TPM_PROCESS_ENABLED'),'N');
9 
10    /* =========================================================
11    --tbl_type to hold the object
12    --This is a private rec type to be used by this API only
13    */
14    TYPE object_rec_type IS RECORD (
15       object_id                     NUMBER
16      ,object_curr                   VARCHAR2 (30));
17 
18    /* =========================================================
19    --tbl_type to hold the amount
20    --This is a private rec type to be used by this API only
21    ============================================================*/
22 
23    TYPE object_tbl_type IS TABLE OF object_rec_type
24       INDEX BY BINARY_INTEGER;
25 
26 ---------------------------------------------------------------------
27 -- PROCEDURE
28 --    validate_lumsum_offer
29 --
30 -- PURPOSE
31 --
32 -- PARAMETERS
33    --p_qp_list_header_id     IN   NUMBER
34    --x_return_status         OUT NOCOPY  VARCHAR2);
35 -- NOTES
36 --           This API will va;idate the lumsum offer distribution
37 -- HISTORY
38 --   09/24/2001  Mumu Pande  Create.
39 ----------------------------------------------------------------------
40 
41 PROCEDURE validate_lumpsum_offer (p_qp_list_header_id IN NUMBER, x_return_status OUT NOCOPY VARCHAR2);
42 --------------------------------------------------------------------------
43     FUNCTION find_org_id (p_actbudget_id IN NUMBER) RETURN number IS
44       l_org_id number := NULL;
45 
46       CURSOR get_fund_org_csr(p_id in number) IS
47       SELECT org_id
48       FROM ozf_funds_all_b
49       WHERE fund_id = p_actbudget_id;
50 
51     BEGIN
52 
53      OPEN  get_fund_org_csr(p_actbudget_id);
54      FETCH get_fund_org_csr INTO l_org_id;
55      CLOSE get_fund_org_csr;
56 
57      RETURN l_org_id;
58 
59     END find_org_id;
60 
61 --------------------------------------------------------------------------
62 --  yzhao: internal procedure called by wf_respond() to fix bug 2741039
63 --------------------------------------------------------------------------
64     PROCEDURE set_org_ctx (p_org_id IN NUMBER) IS
65     BEGIN
66 
67          IF p_org_id is not NULL THEN
68            fnd_client_info.set_org_context(to_char(p_org_id));
69          END IF;
70 
71     END set_org_ctx;
72 
73 --------------------------------------------------------------------------
74 
75 ---------------------------------------------------------------------
76 -- PROCEDURE
77 --    create_budget_amt_utilized
78 --
79 -- PURPOSE
80 --   -- Should be called only by the cost module of OM
81 -- PARAMETERS
82 --      p_act_budget_used_by_id    IN NUMBER  --
83 --     ,p_act_budget_used_by_type  IN VARCHAR2 -- eg. CAMP
84 --     ,p_amount IN NUMBER total amount for utilizing
85 --           x_return_status OUT VARCHAR2
86 --
87 -- NOTES
88 --       This API will create utlizations for camps, schedules,events,offers.event_sche
89 --       in the ozf_Act_budgets table and ozf_Fund_utlized_vl table.
90 --       This API should be called from the cost module of OM only
91 -- HISTORY
92 --    04/27/2001  Mumu Pande  Create.
93 ---------------------------------------------------------------------
94    PROCEDURE create_budget_amt_utilized (
95       p_budget_used_by_id     IN       NUMBER
96      ,p_budget_used_by_type   IN       VARCHAR2
97      ,p_currency              IN       VARCHAR2
98      ,p_cost_tbl              IN       cost_tbl_type
99      ,p_api_version           IN       NUMBER
100      ,p_init_msg_list         IN       VARCHAR2 := fnd_api.g_false
101      ,p_commit                IN       VARCHAR2 := fnd_api.g_false
102      ,p_validation_level      IN       NUMBER := fnd_api.g_valid_level_full
103      ,x_return_status         OUT NOCOPY      VARCHAR2
104      ,x_msg_count             OUT NOCOPY      NUMBER
105      ,x_msg_data              OUT NOCOPY      VARCHAR2
106    ) IS
107       /*
108        CURSOR c_parent_source IS
109           SELECT   parent_src_id, parent_currency, SUM (amount) total_amount
110               FROM (SELECT   a1.parent_source_id parent_src_id, a1.parent_src_curr parent_currency
111                             ,NVL (SUM (a1.parent_src_apprvd_amt), 0) amount
112                         FROM ozf_act_budgets a1
113                        WHERE a1.act_budget_used_by_id = p_budget_used_by_id
114                          AND a1.arc_act_budget_used_by = p_budget_used_by_type
115                          AND a1.status_code = 'APPROVED'
116                          AND a1.transfer_type <> 'UTILIZED'
117                     GROUP BY a1.parent_source_id, a1.parent_src_curr
118                     UNION
119                     SELECT   a2.parent_source_id parent_src_id, a2.parent_src_curr parent_currency
120                             ,-NVL (SUM (a2.parent_src_apprvd_amt), 0) amount
121                         FROM ozf_act_budgets a2
122                        WHERE a2.budget_source_id = p_budget_used_by_id
123                          AND a2.budget_source_type = p_budget_used_by_type
124                          AND a2.status_code = 'APPROVED'
125                     GROUP BY a2.parent_source_id, a2.parent_src_curr)
126           GROUP BY parent_src_id, parent_currency
127           ORDER BY parent_src_id;
128       */
129 /*
130       CURSOR c_parent_source IS
131          SELECT   parent_src_id
132                  ,parent_currency
133                  ,SUM (amount) total_amount
134              FROM (SELECT   a1.fund_id parent_src_id
135                            ,a1.currency_code parent_currency
136                            ,NVL (SUM (a1.amount), 0) amount
137                        FROM ozf_funds_utilized_all_vl a1
138                       WHERE a1.component_id = p_budget_used_by_id
139                         AND a1.component_type = p_budget_used_by_type
140 
141 --                        AND a1.status_code = 'APPROVED' -- only approved record are present here
142                         AND a1.utilization_type IN ('TRANSFER', 'REQUEST')
143                    GROUP BY a1.fund_id, a1.currency_code
144                    UNION
145                    SELECT   a2.fund_id parent_src_id
146                            ,a2.currency_code parent_currency
147                            ,-NVL (SUM (a2.amount), 0) amount
148                        FROM ozf_funds_utilized_all_vl a2
149                       WHERE a2.plan_id = p_budget_used_by_id
150                         AND a2.plan_type = p_budget_used_by_type
151                         AND a2.utilization_type IN ('TRANSFER', 'REQUEST', 'UTILIZED')
152 
153 --                        AND a2.status_code = 'APPROVED' -- -- only approved record are present here
154                    GROUP BY a2.fund_id, a2.currency_code)
155          GROUP BY parent_src_id, parent_currency
156          ORDER BY parent_src_id;
157 */
158 
159 /*
160       CURSOR c_act_util_rec (
161          p_used_by_id      IN   NUMBER
162         ,p_used_by_type    IN   VARCHAR2
163         ,p_parent_src_id   IN   NUMBER
164       ) IS
165          SELECT activity_budget_id
166                ,object_version_number
167                ,approved_amount
168                ,parent_src_apprvd_amt
169            FROM ozf_act_budgets
170           WHERE act_budget_used_by_id = p_used_by_id
171             AND arc_act_budget_used_by = p_used_by_type
172 
173 --            AND parent_source_id = p_parent_src_id
174             AND transfer_type = 'UTILIZED';
175 */
176     --  l_parent_source_rec     c_parent_source%ROWTYPE;
177       l_api_version           NUMBER                                  := 1.0;
178       l_return_status         VARCHAR2 (1)                            := fnd_api.g_ret_sts_success;
179       l_api_name              VARCHAR2 (60)                           := 'create_budget_amount_utilized';
180       l_act_budget_id         NUMBER;
181       l_act_budgets_rec       ozf_actbudgets_pvt.act_budgets_rec_type;
182       l_util_amount           NUMBER                                  := 0;
183       l_amount_remaining      NUMBER                                  := 0;
184       l_full_name    CONSTANT VARCHAR2 (90)                           :=    g_pkg_name
185                                                                          || '.'
186                                                                          || l_api_name;
187       l_amount                NUMBER                                  := 0;
188       l_converted_amt         NUMBER;
189       l_activity_id           NUMBER;
190       l_obj_ver_num           NUMBER;
191       l_old_approved_amount   NUMBER;
192       l_old_parent_src_amt    NUMBER;
193       l_utilized_amount     NUMBER;
194 
195    BEGIN
196       SAVEPOINT create_budget_amt_utilized;
197       x_return_status            := fnd_api.g_ret_sts_success;
198       IF G_DEBUG THEN
199          ozf_utility_pvt.debug_message (': begin ');
200       END IF;
201 
202       IF fnd_api.to_boolean (p_init_msg_list) THEN
203          fnd_msg_pub.initialize;
204       END IF;
205 
206       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
207          RAISE fnd_api.g_exc_unexpected_error;
208       END IF;
209 
210       <<cost_line_tbl_loop>>
211       FOR k IN NVL (p_cost_tbl.FIRST, 1) .. NVL (p_cost_tbl.LAST, 0)
212       LOOP
213          /*   OPEN c_parent_source;
214 
215             <<parent_cur_loop>>
216             LOOP
217                FETCH c_parent_source INTO l_parent_source_rec;
218 
219                -- change later if a error has to be raised or not.
220                IF c_parent_source%NOTFOUND THEN
221                   ozf_utility_pvt.error_message ('OZF_ACT_BUDG_UTIL_OVER');
222                END IF;
223 
224                EXIT WHEN c_parent_source%NOTFOUND;
225           */
226                --- convert the cost currency into the campaign currency
227          IF p_currency = p_cost_tbl (k).cost_curr THEN
228             l_amount                   := p_cost_tbl (k).cost_amount; -- inrequest currency
229          ELSE
230             -- call the currency conversion wrapper
231             ozf_utility_pvt.convert_currency (
232                x_return_status=> x_return_status
233               ,p_from_currency=> p_cost_tbl (k).cost_curr
234               ,p_to_currency=> p_currency
235               ,p_from_amount=> p_cost_tbl (k).cost_amount
236               ,x_to_amount=> l_amount
237             );
238 
239             IF x_return_status <> fnd_api.g_ret_sts_success THEN
240                x_return_status            := fnd_api.g_ret_sts_error;
241                RAISE fnd_api.g_exc_error;
242             END IF;
243          END IF;
244 
245          /*
246           -- convert the object currency amount in to fund currency
247           IF l_parent_source_rec.parent_currency = p_currency THEN
248              l_converted_amt            := l_amount;
249           ELSE
250              -- call the currency conversion wrapper
251              ozf_utility_pvt.convert_currency (
252                 x_return_status=> x_return_status
253                ,p_from_currency=> p_currency
254                ,p_to_currency=> l_parent_source_rec.parent_currency
255                ,p_from_amount=> l_amount
256                ,x_to_amount=> l_converted_amt
257              );
258 
259              IF x_return_status <> fnd_api.g_ret_sts_success THEN
260                 x_return_status            := fnd_api.g_ret_sts_error;
261                 RAISE fnd_api.g_exc_error;
262              END IF;
263           END IF;
264 
265           -- check against the converted amount but update the amount in parent currency
266           IF NVL (l_parent_source_rec.total_amount, 0) >= NVL (l_converted_amt, 0) THEN
267              l_util_amount              := l_amount; -- in req currency
268              l_amount_remaining         :=   l_amount
269                                            - l_util_amount; -- in request currency
270           ELSIF NVL (l_parent_source_rec.total_amount, 0) < NVL (l_converted_amt, 0) THEN
271              -- call the currency conversion wrapper
272              ozf_utility_pvt.convert_currency (
273                 x_return_status=> x_return_status
274                ,p_from_currency=> l_parent_source_rec.parent_currency
275                ,p_to_currency=> p_currency
276                ,p_from_amount=> l_parent_source_rec.total_amount
277                ,x_to_amount=> l_util_amount
278              );
279              l_amount_remaining         :=   l_amount
280                                            - l_util_amount; -- in req currnecy
281           END IF;
282          */
283          l_util_amount              := l_amount; -- in req currency
284          l_amount                   := l_amount_remaining; -- in req currency
285 
286          IF l_util_amount <> 0 THEN
287             -- don't need to convert if currencies are equal
288             l_act_budgets_rec.request_amount := l_util_amount;
289             IF G_DEBUG THEN
290                ozf_utility_pvt.debug_message (   l_full_name
291                                            || ': begin create act budgets ');
292             END IF;
293             l_act_budgets_rec.act_budget_used_by_id := p_budget_used_by_id;
294             l_act_budgets_rec.arc_act_budget_used_by := p_budget_used_by_type;
295             l_act_budgets_rec.budget_source_type := p_budget_used_by_type;
296             l_act_budgets_rec.budget_source_id := p_budget_used_by_id;
297             l_act_budgets_rec.request_currency := p_currency;
298             l_act_budgets_rec.request_date := SYSDATE;
299             l_act_budgets_rec.user_status_id := 5001;
300             l_act_budgets_rec.status_code := 'APPROVED';
301             l_act_budgets_rec.transfer_type := 'UTILIZED';
302             --l_act_budgets_rec.approved_original_amount := l_parent_source_rec.total_amount;
303             --l_act_budgets_rec.approved_in_currency := l_parent_source_rec.total_amount;
304             l_act_budgets_rec.approval_date := SYSDATE;
305             l_act_budgets_rec.approver_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
306             l_act_budgets_rec.justification :=
307                                         TO_CHAR (p_cost_tbl (k).cost_id)
308                                      || p_cost_tbl (k).cost_desc;
309             --  l_act_budgets_rec.parent_source_id := l_parent_source_rec.parent_src_id;
310 
311             --  l_act_budgets_rec.parent_src_curr := l_parent_source_rec.parent_currency;
312 /*
313             OPEN c_act_util_rec (
314                p_budget_used_by_id
315               ,p_budget_used_by_type
316               ,l_parent_source_rec.parent_src_id
317             );
318             FETCH c_act_util_rec INTO l_activity_id, l_obj_ver_num, l_old_approved_amount,l_old_parent_src_amt;
319             CLOSE c_act_util_rec;
320 
321             IF l_activity_id IS NULL THEN
322                l_act_budgets_rec.approved_amount := l_util_amount;
323             l_act_budgets_rec.parent_src_apprvd_amt := l_parent_source_rec.total_amount;
324                ozf_actbudgets_pvt.create_act_budgets (
325                   p_api_version=> l_api_version
326                  ,x_return_status=> l_return_status
327                  ,x_msg_count=> x_msg_count
328                  ,x_msg_data=> x_msg_data
329                  ,p_act_budgets_rec=> l_act_budgets_rec
330                  ,x_act_budget_id=> l_act_budget_id
331                );
332 
333                IF l_return_status = fnd_api.g_ret_sts_error THEN
334                   RAISE fnd_api.g_exc_error;
335                ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
336                   RAISE fnd_api.g_exc_unexpected_error;
337                END IF;
338             ELSE
339                l_act_budgets_rec.request_amount :=   l_old_approved_amount
340                                                    + l_util_amount;
341                l_act_budgets_rec.parent_src_apprvd_amt := l_parent_source_rec.total_amount + l_old_parent_src_amt;
342                l_act_budgets_rec.activity_budget_id := l_activity_id;
343                l_act_budgets_rec.object_version_number := l_obj_ver_num;
344                ozf_actbudgets_pvt.update_act_budgets (
345                   p_api_version=> l_api_version
346                  ,x_return_status=> l_return_status
347                  ,x_msg_count=> x_msg_count
348                  ,x_msg_data=> x_msg_data
349                  ,p_act_budgets_rec=> l_act_budgets_rec
350                );
351             END IF;
352 */
353              process_act_budgets (x_return_status  => l_return_status,
354                                   x_msg_count => x_msg_count,
355                                   x_msg_data   => x_msg_data,
356                                   p_act_budgets_rec => l_act_budgets_rec,
357                                   p_act_util_rec   =>ozf_actbudgets_pvt.G_MISS_ACT_UTIL_REC,
358                                   x_act_budget_id  => l_act_budget_id,
359                                   x_utilized_amount => l_utilized_amount
360                                  ) ;
361 
362             IF l_return_status = fnd_api.g_ret_sts_error THEN
363                RAISE fnd_api.g_exc_error;
364             ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
365                RAISE fnd_api.g_exc_unexpected_error;
366             END IF;
367             --Raise error message if committed amount is less then
368             IF l_util_amount > l_utilized_amount  AND  l_utilized_amount = 0   THEN
369                  IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error) THEN
370                      fnd_message.set_name('OZF', 'OZF_COMMAMT_LESS_REQAMT');
371                      fnd_msg_pub.ADD;
372                  END IF;
373             END IF;
374 
375          END IF;
376 
377           /*
378             EXIT WHEN l_amount_remaining = 0;
379             IF G_DEBUG THEN
380                ozf_utility_pvt.debug_message (   l_full_name
381                                            || ': end create act budgets  ');
382             END IF;
383             l_activity_id              := NULL;
384             l_act_budgets_rec          := NULL;
385             END LOOP parent_cur_loop;
386          */
387          -- initiallize these variable
388 
389          l_amount_remaining         := 0;
390          l_amount                   := 0;
391          l_converted_amt            := 0;
392          l_util_amount              := 0;
393 
394 --         CLOSE c_parent_source;
395       END LOOP cost_line_tbl_loop;
396    EXCEPTION
397       WHEN fnd_api.g_exc_error THEN
398          ROLLBACK TO create_budget_amt_utilized;
399          x_return_status            := fnd_api.g_ret_sts_error;
400          fnd_msg_pub.count_and_get (
401             p_count=> x_msg_count
402            ,p_data=> x_msg_data
403            ,p_encoded=> fnd_api.g_false
404          );
405       WHEN fnd_api.g_exc_unexpected_error THEN
406          ROLLBACK TO create_budget_amt_utilized;
407          x_return_status            := fnd_api.g_ret_sts_unexp_error;
408          fnd_msg_pub.count_and_get (
409             p_count=> x_msg_count
410            ,p_data=> x_msg_data
411            ,p_encoded=> fnd_api.g_false
412          );
413       WHEN OTHERS THEN
414          ROLLBACK TO create_budget_amt_utilized;
415          x_return_status            := fnd_api.g_ret_sts_unexp_error;
416 
417          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
418             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
419          END IF;
420 
421          fnd_msg_pub.count_and_get (
422             p_count=> x_msg_count
423            ,p_data=> x_msg_data
424            ,p_encoded=> fnd_api.g_false
425          );
426    END create_budget_amt_utilized;
427 
428 
429 
430 ---------------------------------------------------------------------
431    -- NAME
432    --    get_parent_Src
433    -- PURPOSE
434    -- API to automaticaly populate the parent_source_id ( fund_id), parent_src_curr, parent_src_apprv_amt
435    -- HISTORY
436    -- 04/27/2001 mpande   Created.
437    -- 08/05/2005 feliu    Use ozf_object_fund_summary table to get committed budgets.
438 ---------------------------------------------------------------------
439 
440    PROCEDURE get_parent_src (
441       p_budget_source_type   IN       VARCHAR2
442      ,p_budget_source_id     IN       NUMBER
443      ,p_amount               IN       NUMBER
444      ,p_req_curr             IN       VARCHAR2
445      ,p_mode                 IN       VARCHAR2 := jtf_plsql_api.g_create
446      ,p_old_amount           IN       NUMBER := 0
447      ,p_exchange_rate_type   IN       VARCHAR2 DEFAULT NULL --Added for bug 7030415
448      ,x_return_status        OUT NOCOPY      VARCHAR2
449      ,x_parent_src_tbl       OUT NOCOPY      parent_src_tbl_type
450    ) IS
451 
452       CURSOR c_parent_source IS
453         SELECT fund_id parent_source
454                ,fund_currency parent_curr
455                ,NVL(committed_amt,0)-NVL(utilized_amt,0) total_amount
456                ,NVL(univ_curr_committed_amt,0)-NVL(univ_curr_utilized_amt,0) total_acctd_amount
457         FROM ozf_object_fund_summary
458         WHERE object_id =p_budget_source_id
459         AND object_type = p_budget_source_type;
460 
461 
462 /*
463              SELECT   parent_source
464                  ,parent_curr
465                  ,SUM (amount) total_amount
466                  ,SUM(acctd_amount) total_acctd_amount
467              FROM (SELECT   a1.fund_id parent_source
468                            ,a1.currency_code parent_curr
469                            ,SUM(NVL(a1.amount, 0)) amount
470                            ,SUM(NVL(a1.acctd_amount,0)) acctd_amount
471                        FROM ozf_funds_utilized_all_b a1
472                        WHERE a1.component_id = p_budget_source_id
473                        AND a1.component_type = p_budget_source_type
474                         AND a1.utilization_type NOT IN
475                                                ('ADJUSTMENT', 'ACCRUAL', 'UTILIZED', 'SALES_ACCRUAL', 'CHARGEBACK')
476                    GROUP BY a1.fund_id, a1.currency_code
477                    UNION
478                    SELECT   a2.fund_id parent_source
479                            ,a2.currency_code parent_curr
480                            ,-SUM(NVL(a2.amount, 0)) amount,
481                                           -SUM(NVL(a2.acctd_amount,0)) acctd_amount
482                        FROM ozf_funds_utilized_all_b a2
483                       WHERE a2.plan_id = p_budget_source_id
484                         AND a2.plan_type =p_budget_source_type
485                    GROUP BY a2.fund_id, a2.currency_code)
486          GROUP BY parent_source, parent_curr
487          ORDER BY parent_source;
488 */
489          CURSOR c_total_acct_amt IS
490            SELECT SUM(NVL(univ_curr_committed_amt,0) - NVL(univ_curr_utilized_amt,0))
491            FROM ozf_object_fund_summary
492            WHERE object_id =p_budget_source_id
493            AND object_type = p_budget_source_type;
494 
495 /*
496                 SELECT   SUM(acctd_amount) total_acctd_amount
497                 FROM (SELECT   SUM(NVL(a1.acctd_amount,0)) acctd_amount
498                               FROM ozf_funds_utilized_all_b a1
499                               WHERE a1.component_id = p_budget_source_id
500                              AND a1.component_type =p_budget_source_type
501                              AND a1.utilization_type NOT IN
502                                                ('ADJUSTMENT', 'ACCRUAL', 'UTILIZED', 'SALES_ACCRUAL', 'CHARGEBACK')
503                              UNION
504                             SELECT -SUM(NVL(a2.acctd_amount,0)) acctd_amount
505                             FROM ozf_funds_utilized_all_b a2
506                             WHERE a2.plan_id = p_budget_source_id
507                             AND a2.plan_type = p_budget_source_type);
508 */
509       l_parent_source_rec   c_parent_source%ROWTYPE;
510       l_converted_amt       NUMBER;
511       p_updated_amount      NUMBER                    := 0;
512       l_counter             NUMBER;
513       l_amount_remaining    NUMBER;
514       l_old_currency        VARCHAR2(30);
515       l_acctd_amount        NUMBER;
516       l_amount              NUMBER;
517       l_total_amount        NUMBER;
518 
519       l_rate                NUMBER;  --Added for bug 7030415
520 
521    BEGIN
522       x_return_status        := fnd_api.g_ret_sts_success;
523       l_total_amount         := p_amount; -- amount in object currency
524       l_counter                  := 1;
525       l_old_currency             := p_req_curr; -- object currency.
526       l_amount_remaining  := p_amount;
527 
528      OPEN c_total_acct_amt;
529      FETCH c_total_acct_amt INTO l_acctd_amount;
530      CLOSE c_total_acct_amt;
531 
532       OPEN c_parent_source;
533       LOOP
534          FETCH c_parent_source INTO l_parent_source_rec;
535          EXIT WHEN c_parent_source%NOTFOUND;
536 
537 --         IF l_parent_source_rec.total_amount <> 0 THEN
538 
539              IF l_acctd_amount = 0 THEN -- no committed amount but g_recal_flag is 'Y', then only create utilization for first budget.
540                 l_amount := l_total_amount;
541              ELSE -- propotional distribute amount based on remaining amount.
542 	        -- Fix for bug # 12868439, rounding of amount is not needed here.
543                 --l_amount := ozf_utility_pvt.currround(l_parent_source_rec.total_acctd_amount / l_acctd_amount * l_total_amount, l_old_currency);
544 		l_amount := l_parent_source_rec.total_acctd_amount / l_acctd_amount * l_total_amount;
545              END IF;
546 
547              l_amount_remaining :=l_amount_remaining - l_amount;
548 
549                 -- This conversion should essentially be based
550                 --on utilization org, since the converted amount is used to populate the
551                 --amount column of utilization table.
552             IF G_DEBUG THEN
553                ozf_utility_pvt.debug_message('parent_curr '|| l_parent_source_rec.parent_curr);
554                ozf_utility_pvt.debug_message('l_old_currency '|| l_old_currency);
555                ozf_utility_pvt.debug_message('l_amount '||l_amount);
556             END IF;
557 
558               IF l_parent_source_rec.parent_curr <> l_old_currency THEN
559                   ozf_utility_pvt.convert_currency (
560                       x_return_status=> x_return_status
561                      ,p_from_currency=> l_old_currency
562                      ,p_to_currency=> l_parent_source_rec.parent_curr
563                      ,p_conv_type=> p_exchange_rate_type --Added for bug 7030415
564                      ,p_from_amount=> l_amount
565                      ,x_to_amount=> l_converted_amt
566                      ,x_rate=>l_rate
567                      );
568                ELSE
569                   l_converted_amt := l_amount;
570                END IF;
571 
572                x_parent_src_tbl (l_counter).fund_id := l_parent_source_rec.parent_source;
573                x_parent_src_tbl (l_counter).fund_curr := l_parent_source_rec.parent_curr;
574                x_parent_src_tbl (l_counter).fund_amount := l_converted_amt;
575                x_parent_src_tbl (l_counter).plan_amount := l_amount;
576                l_counter := l_counter + 1;
577 
578         -- END IF;
579           EXIT WHEN l_acctd_amount = 0; -- for no committed amount.
580           -- could have negative utilization amount. commented by feliu on 08/26/2005.
581           --EXIT WHEN l_amount_remaining <= 0;
582 
583       END LOOP;
584 
585       CLOSE c_parent_source;
586 
587    EXCEPTION
588       WHEN fnd_api.g_exc_error THEN
589          x_return_status            := fnd_api.g_ret_sts_error;
590       WHEN fnd_api.g_exc_unexpected_error THEN
591          x_return_status            := fnd_api.g_ret_sts_unexp_error;
592       WHEN OTHERS THEN
593          x_return_status            := fnd_api.g_ret_sts_unexp_error;
594 
595    END get_parent_src;
596 
597 
598 /*****************************************************************************************/
599 -- Start of Comments
600 -- NAME
601 --    Create Fund Utilization
602 -- PURPOSE
603 --  Create utilizations for the utlized amount of that  activity
604 -- called only from ozf_Act_budgets API for utlized amount creation
605 -- HISTORY
606 -- 02/23/2001  mpande  CREATED
607 -- 02/28/02    feliu   Added condition for manual adjustment.
608 ---------------------------------------------------------------------
609 
610    PROCEDURE create_fund_utilization (
611       p_act_budget_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type
612      ,x_return_status    OUT NOCOPY      VARCHAR2
613      ,x_msg_count        OUT NOCOPY      NUMBER
614      ,x_msg_data         OUT NOCOPY      VARCHAR2
615      ,p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type
616             := ozf_actbudgets_pvt.g_miss_act_util_rec
617    ) IS
618      l_utilized_amount    NUMBER;
619    BEGIN
620      create_fund_utilization (
621         p_act_budget_rec   => p_act_budget_rec
622        ,x_return_status    => x_return_status
623        ,x_msg_count        => x_msg_count
624        ,x_msg_data         => x_msg_data
625        ,p_act_util_rec     => p_act_util_rec
626        ,x_utilized_amount  => l_utilized_amount);
627    END create_fund_utilization;
628 
629 
630 /*****************************************************************************************/
631 -- Start of Comments
632 -- NAME
633 --    Create Fund Utilization
634 -- PURPOSE
635 --  Overloaded create_fund_utilization for bug#8867381.
636 --
637 -- HISTORY
638 -- 27/10/2009  muthsubr CREATED
639 -- 29/11/2011  muthsubr Altered px_ozf_funds_new_rectype to px_ozf_funds_new_tbl
640 --			For TPA Parallel Execution ER - 9614703.
641 ---------------------------------------------------------------------
642 
643    PROCEDURE create_fund_utilization (
644       p_act_budget_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type
645      ,x_return_status    OUT NOCOPY      VARCHAR2
646      ,x_msg_count        OUT NOCOPY      NUMBER
647      ,x_msg_data         OUT NOCOPY      VARCHAR2
648      ,p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type
649             := ozf_actbudgets_pvt.g_miss_act_util_rec
650      ,x_utilized_amount  OUT NOCOPY      NUMBER
651    ) IS
652      l_use_fund_staging_tables VARCHAR2(1):= 'F';
653      lx_ozf_act_budgets_tbl OZF_UTILITY_PVT.ozf_act_budgets_table;
654      lx_ozf_funds_old_rectype OZF_UTILITY_PVT.ozf_funds_all_b_rectype;
655      lx_ozf_funds_new_tbl OZF_UTILITY_PVT.ozf_funds_table;
656      l_batch_type VARCHAR2(30);
657    BEGIN
658      create_fund_utilization (
659         p_act_budget_rec   => p_act_budget_rec
660        ,x_return_status    => x_return_status
661        ,x_msg_count        => x_msg_count
662        ,x_msg_data         => x_msg_data
663        ,p_act_util_rec     => p_act_util_rec
664        ,x_utilized_amount  => x_utilized_amount
665        ,p_batch_type	     =>    l_batch_type
666        ,p_use_fund_staging_tables => l_use_fund_staging_tables
667        ,px_ozf_act_budgets_tbl => lx_ozf_act_budgets_tbl
668        ,px_ozf_funds_old_rectype =>  lx_ozf_funds_old_rectype
669        ,px_ozf_funds_new_tbl =>  lx_ozf_funds_new_tbl        -- For TPA Parallel Execution ER - 9614703
670        );
671    END create_fund_utilization;
672 
673    PROCEDURE create_fund_utilization (
674       p_act_budget_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type
675      ,x_return_status    OUT NOCOPY      VARCHAR2
676      ,x_msg_count        OUT NOCOPY      NUMBER
677      ,x_msg_data         OUT NOCOPY      VARCHAR2
678      ,p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type
679             := ozf_actbudgets_pvt.g_miss_act_util_rec
680      ,x_utilized_amount  OUT NOCOPY      NUMBER
681      ,x_utilization_id OUT NOCOPY      NUMBER
682    ) IS
683      l_use_fund_staging_tables VARCHAR2(1):= 'F';
684      lx_ozf_act_budgets_tbl OZF_UTILITY_PVT.ozf_act_budgets_table;
685      lx_ozf_funds_old_rectype OZF_UTILITY_PVT.ozf_funds_all_b_rectype;
686      lx_ozf_funds_new_tbl OZF_UTILITY_PVT.ozf_funds_table;
687      l_batch_type VARCHAR2(30);
688    BEGIN
689      create_fund_utilization (
690         p_act_budget_rec   => p_act_budget_rec
691        ,x_return_status    => x_return_status
692        ,x_msg_count        => x_msg_count
693        ,x_msg_data         => x_msg_data
694        ,p_act_util_rec     => p_act_util_rec
695        ,x_utilized_amount  => x_utilized_amount
696        ,p_batch_type	     =>    l_batch_type
697        ,p_use_fund_staging_tables => l_use_fund_staging_tables
698        ,px_ozf_act_budgets_tbl => lx_ozf_act_budgets_tbl
699        ,px_ozf_funds_old_rectype =>  lx_ozf_funds_old_rectype
700        ,px_ozf_funds_new_tbl =>  lx_ozf_funds_new_tbl     -- For TPA Parallel Execution ER - 9614703
701        ,x_utilization_id => x_utilization_id
702        );
703    END create_fund_utilization;
704 
705     PROCEDURE create_fund_utilization (
706       p_act_budget_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type
707      ,x_return_status    OUT NOCOPY      VARCHAR2
708      ,x_msg_count        OUT NOCOPY      NUMBER
709      ,x_msg_data         OUT NOCOPY      VARCHAR2
710      ,p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type
711             := ozf_actbudgets_pvt.g_miss_act_util_rec
712      ,x_utilized_amount  OUT NOCOPY      NUMBER
713      ,p_batch_type	     IN  VARCHAR2
714      ,p_use_fund_staging_tables IN      VARCHAR2
715      ,px_ozf_act_budgets_tbl IN OUT NOCOPY  OZF_UTILITY_PVT.ozf_act_budgets_table
716      ,px_ozf_funds_old_rectype  IN      OZF_UTILITY_PVT.ozf_funds_all_b_rectype
717      ,px_ozf_funds_new_tbl  IN OUT NOCOPY   OZF_UTILITY_PVT.ozf_funds_table
718    ) IS
719      l_utilization_id NUMBER;
720    BEGIN
721 
722      --kdass - added for Bug 8726683
723      create_fund_utilization (
724         p_act_budget_rec   => p_act_budget_rec
725        ,x_return_status    => x_return_status
726        ,x_msg_count        => x_msg_count
727        ,x_msg_data         => x_msg_data
728        ,p_act_util_rec     => p_act_util_rec
729        ,x_utilized_amount  => x_utilized_amount
730        ,p_batch_type	     =>    p_batch_type
731        ,p_use_fund_staging_tables => p_use_fund_staging_tables
732        ,px_ozf_act_budgets_tbl => px_ozf_act_budgets_tbl
733        ,px_ozf_funds_old_rectype =>  px_ozf_funds_old_rectype
734        ,px_ozf_funds_new_tbl =>  px_ozf_funds_new_tbl  -- For TPA Parallel Execution ER - 9614703
735        ,x_utilization_id   => l_utilization_id
736        );
737    END create_fund_utilization;
738 
739 
740 /*****************************************************************************************/
741 -- Start of Comments
742 -- NAME
743 --    Create Fund Utilization
744 -- PURPOSE
745 --  Create utilizations for the utlized amount of that  activity
746 --   called only from ozf_Act_budgets API for utlized amount creation
747 -- HISTORY
748 -- 02/23/2001  mpande  CREATED
749 -- 02/28/02    feliu   Added condition for manual adjustment.
750 -- 06/21/2004  yzhao   Added x_utilized_amount to return actual utilized amount
751 -- 27/10/2009  muthsubr Added px_ozf_act_budgets_tbl, p_use_fund_staging_tables
752 --                      px_ozf_funds_old_rectype, px_ozf_funds_new_rectype
753 --                      for bug#8867381.
754 -- 29/11/2010  muthsubr Altered px_ozf_funds_new_rectype to px_ozf_funds_new_tbl
755 --			for TPA Parallel Execution ERBug#9614703.
756 ---------------------------------------------------------------------
757 
758    PROCEDURE create_fund_utilization (
759       p_act_budget_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type
760      ,x_return_status    OUT NOCOPY      VARCHAR2
761      ,x_msg_count        OUT NOCOPY      NUMBER
762      ,x_msg_data         OUT NOCOPY      VARCHAR2
763      ,p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type
764             := ozf_actbudgets_pvt.g_miss_act_util_rec
765      ,x_utilized_amount  OUT NOCOPY      NUMBER
766      ,p_batch_type	     IN  VARCHAR2
767      ,p_use_fund_staging_tables IN      VARCHAR2
768      ,px_ozf_act_budgets_tbl IN OUT NOCOPY  OZF_UTILITY_PVT.ozf_act_budgets_table
769      ,px_ozf_funds_old_rectype  IN      OZF_UTILITY_PVT.ozf_funds_all_b_rectype
770      ,px_ozf_funds_new_tbl  IN OUT NOCOPY   OZF_UTILITY_PVT.ozf_funds_table
771      ,x_utilization_id   OUT NOCOPY      NUMBER
772    ) IS
773        l_api_version         CONSTANT NUMBER                                     := 1.0;
774       l_api_name            CONSTANT VARCHAR2 (30)                              := 'create_fund_utilization';
775       l_full_name           CONSTANT VARCHAR2 (60)                              :=    g_pkg_name
776                                                                                    || '.'
777                                                                                    || l_api_name;
778      l_util_rec                 ozf_fund_utilized_pvt.utilization_rec_type;
779       --l_util_id                  NUMBER;
780       l_util_amount              NUMBER;
781       l_return_status            VARCHAR2 (1)                               := fnd_api.g_ret_sts_success;
782       l_obj_number               NUMBER;
783       l_parent_src_tbl           parent_src_tbl_type;
784       l_fund_transfer_flag       VARCHAR2 (1)                               := 'N';
785       l_offer_type               VARCHAR2 (30);
786       l_qlf_type                 VARCHAR2 (30);
787       l_qlf_id                   NUMBER;
788       l_src_fund_type            VARCHAR2 (30);
789       l_src_fund_accrual_basis   VARCHAR2 (30);
790       l_accrual_flag             VARCHAR2 (1);
791       l_plan_id                  NUMBER;
792       l_budget_offer_yn          VARCHAR2(1) := 'N';
793       l_fund_id                  NUMBER;
794       l_accrual_basis            VARCHAR2 (30);
795       l_fund_currency            VARCHAR2 (30);
796       l_total_amount             NUMBER;
797       l_cust_account_id          NUMBER;
798       l_bill_to_site_id          NUMBER;
799       l_beneficiary_account_id   NUMBER;
800       l_check_request           VARCHAR2 (10);
801 
802       --Added variables/c_org_id for bugfix 6278466
803       l_org_id                   NUMBER;
804       l_autopay_party_id         NUMBER;
805 
806       l_autopay_party_attr       VARCHAR2(30);
807 
808       CURSOR c_org_id (p_site_use_id IN NUMBER) IS
809          SELECT org_id
810            FROM hz_cust_site_uses_all
811           WHERE site_use_id = p_site_use_id;
812 
813       -- 11/13/2001 mpande removed qualifier type
814       -- Added autopay_party_id for bugfix 6278466
815       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
816          SELECT offer_type
817                ,qualifier_id,qualifier_type,NVL(budget_offer_yn,'N'),beneficiary_account_id,
818                autopay_party_attr,autopay_party_id
819            FROM ozf_offers
820           WHERE qp_list_header_id = p_offer_id;
821 
822       CURSOR c_funds (p_ofr_fund_id IN NUMBER) IS
823          SELECT fund_type
824                ,accrual_basis,plan_id
825            FROM ozf_funds_all_b
826           WHERE fund_id = p_ofr_fund_id;
827       -- 6/13/2002 mpande added for deal type ofer
828       CURSOR c_accrual_flag (p_price_adjustment_id IN NUMBER) IS
829          SELECT NVL(accrual_flag,'N')
830            FROM oe_price_adjustments
831           WHERE price_Adjustment_id = p_price_Adjustment_id;
832 
833       -- 07/30/03 feliu added for accrual budget.
834       CURSOR c_fund_plan (p_plan_id IN NUMBER) IS
835         SELECT fund_id , currency_code_tc, accrual_basis
836         FROM ozf_funds_all_b
837         WHERE plan_id = p_plan_id;
838 
839       -- 18-JAN-05 kdass get the cust_account_id from cust_acct_site_id
840       -- rimehrot for R12, added bill_to_site_use_id
841       CURSOR c_cust_account_id (p_site_use_id IN NUMBER) IS
842         SELECT sites.cust_account_id, uses.bill_to_site_use_id
843            FROM hz_cust_acct_sites_all sites, hz_cust_site_uses_all uses
844            WHERE uses.site_use_id = p_site_use_id
845              AND sites.cust_acct_site_id = uses.cust_acct_site_id;
846 
847      CURSOR c_get_cust_account_id(p_party_id IN NUMBER) IS
848         select max(cust_account_id) from hz_cust_accounts
849         where party_id = p_party_id
850         and status= 'A';
851 
852         -- rimehrot, bug fix 4030022
853       CURSOR c_check_budget_request(p_offer_id IN NUMBER, p_fund_id IN NUMBER) IS
854       SELECT 'X' FROM ozf_act_budgets
855       WHERE act_budget_used_by_id = p_offer_id
856       AND budget_source_id = p_fund_id
857       AND status_code ='APPROVED'
858       AND transfer_type = 'REQUEST';
859 
860       --Added for bug 7030415
861 
862        CURSOR c_get_conversion_type( p_org_id IN NUMBER) IS
863        SELECT exchange_rate_type
864        FROM   ozf_sys_parameters_all
865        WHERE  org_id = p_org_id;
866 
867 
868       l_exchange_rate_type      VARCHAR2(30) := FND_API.G_MISS_CHAR;
869       l_rate                    NUMBER;
870       l_fund_reconc_msg         VARCHAR2(4000);
871       l_act_bud_cst_msg         VARCHAR2(4000);
872 
873 
874    BEGIN
875         SAVEPOINT create_utilization;
876 
877       l_total_amount := 0;
878       --Added for bug 7425189
879       l_fund_reconc_msg := fnd_message.get_string ('OZF', 'OZF_FUND_RECONCILE');
880       l_act_bud_cst_msg := fnd_message.get_string ('OZF', 'OZF_ACT_BUDG_CST_UTIL');
881 
882 
883       IF l_fund_transfer_flag = 'N' THEN
884          -- 01/02/2002 mpande changed for utilization changes
885          IF p_act_budget_rec.budget_source_type = 'FUND' THEN
886             l_parent_src_tbl (1).fund_id := p_act_budget_rec.budget_source_id;
887             l_parent_src_tbl (1).fund_curr := p_act_budget_rec.approved_in_currency;
888             l_parent_src_tbl (1).fund_amount := p_act_budget_rec.approved_original_amount;
889             l_parent_src_tbl (1).plan_amount := p_act_budget_rec.approved_original_amount;
890          ELSIF      p_act_budget_rec.transfer_type = 'TRANSFER'
891                 AND p_act_budget_rec.arc_act_budget_used_by = 'FUND' THEN
892             l_parent_src_tbl (1).fund_id := p_act_budget_rec.act_budget_used_by_id;
893             -- 12/18/2001 changed here for currency change ***
894             /*l_parent_src_tbl (1).fund_curr := p_act_budget_rec.approved_in_currency;
895               l_parent_src_tbl (1).fund_amount := p_act_budget_rec.approved_original_amount;
896             */
897             l_parent_src_tbl (1).fund_curr := p_act_budget_rec.request_currency;
898             l_parent_src_tbl (1).fund_amount := p_act_budget_rec.approved_amount;
899             l_parent_src_tbl (1).plan_amount := p_act_budget_rec.approved_amount;
900 
901 /*         ELSIF      p_act_budget_rec.transfer_type = 'UTILIZED'
902                 AND p_act_budget_rec.arc_act_budget_used_by IN ('OFFR','CAMP','EVEH','DELV') THEN
903             l_parent_src_tbl (1).fund_id := p_act_budget_rec.act_budget_used_by_id;
904             l_parent_src_tbl (1).fund_curr := p_act_budget_rec.approved_in_currency;
905             l_parent_src_tbl (1).fund_amount := p_act_budget_rec.approved_original_amount;
906             */
907 
908          ELSE
909             IF p_act_budget_rec.transfer_type = 'UTILIZED' THEN
910                -- added by feliu to fix bug for accrual budget.
911                IF p_act_budget_rec.budget_source_type = 'OFFR' THEN
912                        OPEN c_offer_type (p_act_budget_rec.budget_source_id);
913                        --Added l_autopay_party_id for bugfix 6278466
914                        FETCH c_offer_type INTO l_offer_type, l_qlf_id,l_qlf_type,l_budget_offer_yn,l_beneficiary_account_id,
915                                                l_autopay_party_attr,l_autopay_party_id;
916                        CLOSE c_offer_type;
917                END IF;
918 
919                --Added for bug 7030415
920                IF p_act_util_rec.exchange_rate_type IS NULL
921                OR p_act_util_rec.exchange_rate_type = fnd_api.g_miss_char THEN
922                OPEN c_get_conversion_type(p_act_util_rec.org_id);
923                FETCH c_get_conversion_type INTO l_exchange_rate_type;
924                CLOSE c_get_conversion_type;
925 
926                ELSE
927                   l_exchange_rate_type := p_act_util_rec.exchange_rate_type;
928                END IF;
929                -- For accrual budget, do not fetch committed amount.
930                IF l_budget_offer_yn = 'Y' THEN
931                        OPEN c_fund_plan (p_act_budget_rec.budget_source_id);
932                        FETCH c_fund_plan INTO l_fund_id,l_fund_currency,l_accrual_basis;
933                        CLOSE c_fund_plan;
934 
935                   --05/06/2004  kdass fix for bug 3586046
936                   --08/18/2005  feliu fix for third party accrual.
937                /*   IF l_accrual_basis ='CUSTOMER' THEN
938                      IF p_act_budget_rec.parent_source_id <> l_fund_id THEN
939                         fnd_message.set_name ('OZF', 'OZF_FUND_OFFR_ADJ');
940                         fnd_msg_pub.ADD;
941                         RAISE fnd_api.g_exc_error;
942                      END IF;
943                */
944                --Added for bug 7030415, In case of accrual budget.
945                --Need to use the org_id since the converted amount is used to populate
946                --the amount column of utilization table. p_act_util_rec.org_id
947 
948 
949                IF p_act_budget_rec.request_currency  <>l_fund_currency THEN
950 
951                   IF G_DEBUG THEN
952                      ozf_utility_pvt.debug_message (   l_full_name
953                              || ' p_act_budget_rec.exchange_rate_date1: ' || p_act_budget_rec.exchange_rate_date);
954                   END IF;
955 
956                  --Added for bug 7425189
957                  IF p_act_budget_rec.justification IN (l_fund_reconc_msg,l_act_bud_cst_msg)
958                  AND p_act_budget_rec.exchange_rate_date IS NOT NULL THEN
959                     ozf_utility_pvt.convert_currency (
960                     x_return_status=> l_return_status,
961                     p_from_currency=> p_act_budget_rec.request_currency,
962                     p_to_currency=> l_fund_currency,
963                     p_conv_date=> p_act_budget_rec.exchange_rate_date,
964                     p_from_amount=> p_act_budget_rec.approved_amount,
965                     x_to_amount=> l_util_amount,
966                     x_rate=>l_rate
967                    );
968                  ELSE
969                     ozf_utility_pvt.convert_currency (
970                     x_return_status => l_return_status,
971                     p_from_currency => p_act_budget_rec.request_currency,
972                     p_to_currency   => l_fund_currency,
973                     p_conv_type     => l_exchange_rate_type,
974                     p_conv_date     => p_act_budget_rec.exchange_rate_date, --bug 8532055
975                     p_from_amount   => p_act_budget_rec.approved_amount,
976                     x_to_amount     => l_util_amount,
977                     x_rate          =>l_rate
978                    );
979                   END IF;
980 
981                 ELSE
982                   l_util_amount := p_act_budget_rec.request_amount;
983                 END IF;
984 
985                      l_parent_src_tbl (1).fund_id := l_fund_id;
986                      l_parent_src_tbl (1).fund_curr := l_fund_currency;
987                      l_parent_src_tbl (1).fund_amount := l_util_amount;
988                      l_parent_src_tbl (1).plan_amount :=p_act_budget_rec.request_amount;
989 
990                      IF G_DEBUG THEN
991                         ozf_utility_pvt.debug_message (':for accrual budget ' || l_util_amount );
992                      END IF;
993                   -- for SALES budget, should same as customer accrual.
994                   --08/18/2005  feliu fix for third party accrual.
995                 /*  ELSE
996                      l_parent_src_tbl (1).fund_id := p_act_budget_rec.parent_source_id; --l_fund_id;
997                      l_parent_src_tbl (1).fund_curr := p_act_budget_rec.parent_src_curr;--l_fund_currency;
998                      l_parent_src_tbl (1).fund_amount := p_act_budget_rec.parent_src_apprvd_amt;--l_util_amount;
999                      l_parent_src_tbl (1).plan_amount := p_act_budget_rec.request_amount;
1000                 */
1001                 --END IF;
1002 
1003            -- end of  accrual budget.
1004 
1005 
1006                ELSIF    p_act_budget_rec.parent_source_id IS NULL
1007                   OR p_act_budget_rec.parent_source_id = fnd_api.g_miss_num THEN
1008                   --Added for bug 7030415 , For fixed budget
1009                   --nirprasa,12.2 adjustment_net_accrual flow comes to this else condition.
1010                   --While updating ozf_act_budgets 'UTILIZED' recs, p_act_util_rec.plan_curr_amount
1011                   --holds the amount in plan currency. SO send this amount for conversion to budget's curr.
1012                   IF G_DEBUG THEN
1013                    ozf_utility_pvt.debug_message('budget_source_type '|| p_act_budget_rec.budget_source_type);
1014                    ozf_utility_pvt.debug_message('p_act_budget_rec.approved_amount '|| p_act_budget_rec.approved_amount);
1015                    ozf_utility_pvt.debug_message('p_act_budget_rec.request_currency '|| p_act_budget_rec.request_currency);
1016                    ozf_utility_pvt.debug_message('p_act_util_rec.plan_curr_amount '|| p_act_util_rec.plan_curr_amount);
1017                    ozf_utility_pvt.debug_message('p_act_util_rec.plan_currency_code '|| p_act_util_rec.plan_currency_code);
1018                   END IF;
1019                   IF p_act_util_rec.plan_curr_amount IS NULL
1020                   OR p_act_util_rec.plan_curr_amount = FND_API.G_MISS_NUM THEN
1021                   get_parent_src (
1022                      p_budget_source_type=> p_act_budget_rec.budget_source_type
1023                     ,p_budget_source_id=> p_act_budget_rec.budget_source_id
1024                     ,p_amount=> p_act_budget_rec.approved_amount
1025                     ,p_req_curr=> p_act_budget_rec.request_currency
1026                     ,p_exchange_rate_type=>l_exchange_rate_type
1027                     ,x_return_status=> l_return_status
1028                     ,x_parent_src_tbl=> l_parent_src_tbl
1029                   );
1030                   ELSE
1031                   get_parent_src (
1032                      p_budget_source_type=> p_act_budget_rec.budget_source_type
1033                     ,p_budget_source_id=> p_act_budget_rec.budget_source_id
1034                     ,p_amount=> p_act_util_rec.plan_curr_amount
1035                     ,p_req_curr=> p_act_budget_rec.request_currency
1036                     ,p_exchange_rate_type=>l_exchange_rate_type
1037                     ,x_return_status=> l_return_status
1038                     ,x_parent_src_tbl=> l_parent_src_tbl
1039                   );
1040                   END IF;
1041                  /*
1042                   IF l_return_status = fnd_api.g_ret_sts_error THEN
1043                       RAISE fnd_api.g_exc_error;
1044                   ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1045                       RAISE fnd_api.g_exc_unexpected_error;
1046                   END IF;
1047 */               ELSE
1048                   l_parent_src_tbl (1).fund_id := p_act_budget_rec.parent_source_id;
1049                   l_parent_src_tbl (1).fund_curr := p_act_budget_rec.parent_src_curr;
1050                   l_parent_src_tbl (1).fund_amount := p_act_budget_rec.parent_src_apprvd_amt;
1051                   l_parent_src_tbl (1).plan_amount := p_act_budget_rec.request_amount;
1052                END IF;
1053 
1054             ELSE
1055 
1056                get_parent_src (
1057                   p_budget_source_type=> p_act_budget_rec.budget_source_type
1058                  ,p_budget_source_id=> p_act_budget_rec.budget_source_id
1059                  ,p_amount=> p_act_budget_rec.approved_amount
1060                  ,p_req_curr=> p_act_budget_rec.request_currency
1061                  ,p_exchange_rate_type=>l_exchange_rate_type
1062                  ,x_return_status=> l_return_status
1063                  ,x_parent_src_tbl=> l_parent_src_tbl
1064                );
1065   /*             IF l_return_status = fnd_api.g_ret_sts_error THEN
1066                       RAISE fnd_api.g_exc_error;
1067                ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1068                       RAISE fnd_api.g_exc_unexpected_error;
1069                END IF;
1070         */    END IF;
1071          END IF;
1072       END IF;
1073 
1074       IF G_DEBUG THEN
1075          ozf_utility_pvt.debug_message(l_full_name||' : '||'g_recal_flag:   '||g_recal_flag);
1076       END IF;
1077 
1078       FOR i IN NVL (l_parent_src_tbl.FIRST, 1) .. NVL (l_parent_src_tbl.LAST, 0)
1079       LOOP
1080          l_util_rec := null;  -- fixed bug 5124036.
1081          l_total_amount := l_total_amount + NVL (l_parent_src_tbl (i).plan_amount, 0);
1082          -- Added condition by feliu on 02/25/02
1083          IF p_act_util_rec.utilization_type is NULL OR
1084              p_act_util_rec.utilization_type  = fnd_api.g_miss_char THEN
1085             l_util_rec.utilization_type := p_act_budget_rec.transfer_type;
1086          ELSE
1087             l_util_rec.utilization_type := p_act_util_rec.utilization_type;
1088          END IF;
1089 
1090 
1091          l_util_rec.fund_id         := l_parent_src_tbl (i).fund_id;
1092          l_util_rec.plan_type       := p_act_budget_rec.budget_source_type;
1093          l_util_rec.plan_id         := p_act_budget_rec.budget_source_id;
1094          l_util_rec.component_type  := p_act_budget_rec.arc_act_budget_used_by;
1095          l_util_rec.component_id    := p_act_budget_rec.act_budget_used_by_id;
1096          l_util_rec.ams_activity_budget_id := p_act_budget_rec.activity_budget_id;
1097          l_util_rec.amount          := NVL (l_parent_src_tbl (i).fund_amount, 0);
1098          l_util_rec.currency_code   := l_parent_src_tbl (i).fund_curr;
1099          /* Added on 10/18/2001 by feliu for recalculating committed.*/
1100          l_util_rec.adjustment_type_id := p_act_util_rec.adjustment_type_id;
1101          l_util_rec.adjustment_type := p_act_util_rec.adjustment_type;
1102          --l_util_rec.recal_comm_flag := p_act_util_rec.recal_comm_flag;
1103          /* Added on 02/08/2002 by Mpande */
1104          l_util_rec.adjustment_desc := p_act_budget_rec.justification;
1105          l_util_rec.object_type     := p_act_util_rec.object_type;
1106          l_util_rec.object_id       := p_act_util_rec.object_id;
1107          l_util_rec.camp_schedule_id := p_act_util_rec.camp_schedule_id;
1108          l_util_rec.product_level_type := p_act_util_rec.product_level_type;
1109          l_util_rec.product_id      := p_act_util_rec.product_id;
1110          l_util_rec.cust_account_id := p_act_util_rec.cust_account_id;
1111          l_util_rec.price_adjustment_id := p_act_util_rec.price_adjustment_id;
1112 	 -- bug fix 13552986
1113          l_util_rec.adjustment_date := p_act_util_rec.adjustment_date;
1114          l_util_rec.gl_date := p_act_util_rec.gl_date;
1115          /* added by feliu for 11.5.9 */
1116          l_util_rec.activity_product_id := p_act_util_rec.activity_product_id;
1117          l_util_rec.scan_unit := p_act_util_rec.scan_unit;
1118          l_util_rec.scan_unit_remaining := p_act_util_rec.scan_unit_remaining;
1119          l_util_rec.volume_offer_tiers_id := p_act_util_rec.volume_offer_tiers_id;
1120          /* added by yzhao for 11.5.10 */
1121          l_util_rec.reference_type := p_act_util_rec.reference_type;
1122          l_util_rec.reference_id := p_act_util_rec.reference_id;
1123          l_util_rec.billto_cust_account_id := p_act_util_rec.billto_cust_account_id;
1124            /*added by feliu for 11.5.10 */
1125          l_util_rec.order_line_id := p_act_util_rec.order_line_id;
1126          l_util_rec.org_id := p_act_util_rec.org_id;
1127            /*added by feliu for 11.5.10 */
1128          l_util_rec.gl_posted_flag := p_act_util_rec.gl_posted_flag;
1129          l_util_rec.orig_utilization_id := p_act_util_rec.orig_utilization_id;
1130            /* added by rimehrot for R12 */
1131          l_util_rec.bill_to_site_use_id := p_act_util_rec.bill_to_site_use_id;
1132          l_util_rec.ship_to_site_use_id := p_act_util_rec.ship_to_site_use_id;
1133            /* added by kdass for R12 */
1134          l_util_rec.gl_account_credit := p_act_util_rec.gl_account_credit;
1135          l_util_rec.gl_account_debit  := p_act_util_rec.gl_account_debit;
1136 	 l_util_rec.list_line_id  := p_act_util_rec.list_line_id;
1137 
1138 
1139 
1140          --fix for bug 6657242
1141          l_util_rec.site_use_id := p_act_util_rec.site_use_id;
1142 
1143          --nirprasa, assign the amounts so as to skip conversion and rounding later.
1144          --for bugs 7505085, 7425189
1145          IF G_DEBUG THEN
1146          ozf_utility_pvt.debug_message ('ozfvadjb p_act_budget_rec.request_amount '||p_act_budget_rec.request_amount);
1147          END IF;
1148          IF p_act_util_rec.plan_curr_amount IS NULL
1149          OR p_act_util_rec.plan_curr_amount = FND_API.G_MISS_NUM THEN
1150          l_util_rec.plan_curr_amount := p_act_budget_rec.request_amount;
1151          l_util_rec.plan_curr_amount_remaining := p_act_budget_rec.request_amount;
1152          ELSE
1153             l_util_rec.plan_curr_amount           := p_act_util_rec.plan_curr_amount;
1154             l_util_rec.plan_curr_amount_remaining := p_act_util_rec.plan_curr_amount_remaining;
1155          END IF;
1156 
1157 
1158          l_util_rec.plan_currency_code         := p_act_util_rec.plan_currency_code;
1159          l_util_rec.fund_request_currency_code := p_act_util_rec.fund_request_currency_code;
1160 
1161          l_util_rec.exchange_rate_date         := p_act_util_rec.exchange_rate_date;
1162          l_util_rec.exchange_rate_type         := p_act_util_rec.exchange_rate_type;
1163          -- nirprasa,12.2 no need to assign the currency_code column. Its already assigned above.
1164 
1165          --kdass added flexfields
1166          l_util_rec.attribute_category  := p_act_util_rec.attribute_category;
1167          l_util_rec.attribute1  := p_act_util_rec.attribute1;
1168          l_util_rec.attribute2  := p_act_util_rec.attribute2;
1169          l_util_rec.attribute3  := p_act_util_rec.attribute3;
1170          l_util_rec.attribute4  := p_act_util_rec.attribute4;
1171          l_util_rec.attribute5  := p_act_util_rec.attribute5;
1172          l_util_rec.attribute6  := p_act_util_rec.attribute6;
1173          l_util_rec.attribute7  := p_act_util_rec.attribute7;
1174          l_util_rec.attribute8  := p_act_util_rec.attribute8;
1175          l_util_rec.attribute9  := p_act_util_rec.attribute9;
1176          l_util_rec.attribute10  := p_act_util_rec.attribute10;
1177          l_util_rec.attribute11  := p_act_util_rec.attribute11;
1178          l_util_rec.attribute12  := p_act_util_rec.attribute12;
1179          l_util_rec.attribute13  := p_act_util_rec.attribute13;
1180          l_util_rec.attribute14  := p_act_util_rec.attribute14;
1181          l_util_rec.attribute15  := p_act_util_rec.attribute15;
1182 
1183 	 l_util_rec.adjustment_date  := p_act_util_rec.adjustment_date;
1184 
1185          IF  l_util_rec.utilization_type IN ('LEAD_ACCRUAL', 'ACCRUAL') THEN
1186              -- yzhao: 11.5.10 02/12/2004 fix bug 3438414 - MASS1R10 UNABLE TO QUERY EARNINGS AGAINST NET ACCRUAL OFFERS
1187              IF l_util_rec.amount_remaining IS NULL THEN
1188                 l_util_rec.amount_remaining := l_util_rec.amount;
1189              END IF;
1190          ELSIF  l_util_rec.utilization_type = 'UTILIZED' THEN
1191 	 --firx for bug 13406517
1192 	 IF l_util_rec.adjustment_date IS NULL THEN
1193             l_util_rec.adjustment_date := SYSDATE;
1194          END IF;
1195            --  l_util_rec.adjustment_date := sysdate;
1196              -- yzhao: 10/20/2003 added PRIC for price list
1197              IF l_util_rec.plan_type = 'PRIC' THEN
1198                 l_util_rec.utilization_type := 'ADJUSTMENT';
1199                 l_util_rec.amount_remaining := l_util_rec.amount;
1200              ELSIF l_util_rec.plan_type = 'OFFR' THEN
1201                 OPEN c_funds (l_util_rec.fund_id);
1202                 FETCH c_funds INTO l_src_fund_type, l_src_fund_accrual_basis,l_plan_id;
1203                 CLOSE c_funds;
1204                 --for budget source from sales accrual budget.
1205                 IF l_plan_id IS NOT NULL AND l_plan_id <> FND_API.g_miss_num THEN
1206                    IF l_plan_id <>  l_util_rec.component_id  THEN
1207                       l_src_fund_type := 'FIXED' ;
1208                    END IF;
1209                 END IF;
1210                 -- fix bug 4569075 by feliu on 08/25/2005 to populate benefiticary_account_id
1211                 IF l_util_rec.billto_cust_account_id IS NULL THEN
1212                   --kdass 23-FEB-2004 fix for bug 3426061
1213                   -- If the Qualifier is a Buying group, then store Customer Account ID instead of Party ID
1214                   IF l_qlf_type = 'BUYER' THEN
1215                      OPEN c_get_cust_account_id(l_qlf_id);
1216                      FETCH c_get_cust_account_id INTO l_cust_account_id;
1217                      CLOSE c_get_cust_account_id;
1218 
1219                   -- kdass 18-JAN-05 Bug 4125112, if qualifier_type is 'BILL_TO' or 'SHIP_TO', then qualifier_id
1220                   -- is cust account site id. Query hz tables to get cust_account_id.
1221                   ELSIF l_qlf_type IN ('CUSTOMER_BILL_TO', 'SHIP_TO') THEN
1222                      OPEN c_cust_account_id (l_qlf_id);
1223                      FETCH c_cust_account_id INTO l_cust_account_id, l_bill_to_site_id;
1224                      CLOSE c_cust_account_id;
1225                      IF l_qlf_type = 'CUSTOMER_BILL_TO' THEN
1226                         l_util_rec.bill_to_site_use_id := l_qlf_id;
1227                      ELSIF l_qlf_type = 'SHIP_TO' THEN
1228                         l_util_rec.bill_to_site_use_id := l_bill_to_site_id;
1229                         l_util_rec.ship_to_site_use_id := l_qlf_id;
1230                      END IF;
1231                   ELSE
1232                      l_cust_account_id := l_qlf_id;
1233                   END IF;
1234 
1235                   l_util_rec.billto_cust_account_id := l_cust_account_id;
1236 
1237                 END IF; -- end of   l_util_rec.billto_cust_account_id
1238                 IF l_util_rec.cust_account_id IS NULL THEN
1239                    IF l_beneficiary_account_id IS NOT NULL THEN
1240                     IF l_autopay_party_attr <> 'CUSTOMER' AND l_autopay_party_attr IS NOT NULL THEN
1241                       --Added c_org_id for bugfix 6278466
1242                       OPEN c_org_id (l_autopay_party_id);
1243                       FETCH c_org_id INTO l_org_id;
1244                       CLOSE c_org_id;
1245                       l_util_rec.org_id := l_org_id;
1246                     END IF;
1247                       l_util_rec.cust_account_id := l_beneficiary_account_id;
1248                    ELSE
1249                       l_util_rec.cust_account_id := l_util_rec.billto_cust_account_id;
1250                    END IF;
1251                 END IF; -- l_util_rec.cust_account_id
1252 
1253               -- end of bug fix 4569075
1254 
1255                 IF l_src_fund_type = 'FIXED' THEN
1256                    IF l_offer_type IN ('ACCRUAL','LUMPSUM','SCAN_DATA','NET_ACCRUAL') THEN
1257                          l_util_rec.utilization_type := 'ACCRUAL';
1258                          --l_util_rec.adjustment_type_id := NULL;
1259                          --l_util_rec.adjustment_type := NULL;
1260                          l_util_rec.amount_remaining := l_parent_src_tbl (i).fund_amount;
1261                 /*         IF l_offer_type = 'LUMPSUM' THEN
1262                             l_util_rec.cust_account_id := l_qlf_id;
1263                             -- kdass 18-JAN-05 Bug 4125112, if qualifier_type is 'BILL_TO' or 'SHIP_TO', then qualifier_id
1264                             -- is cust account site id. Query hz tables to get cust_account_id.
1265                             IF l_qlf_type IN ('CUSTOMER_BILL_TO', 'SHIP_TO') THEN
1266                                OPEN c_cust_account_id (l_qlf_id);
1267                                FETCH c_cust_account_id INTO l_cust_account_id, l_bill_to_site_id;
1268                                CLOSE c_cust_account_id;
1269                                l_util_rec.cust_account_id := l_cust_account_id;
1270                             END IF;
1271                          END IF;
1272                   */
1273                    ELSIF l_offer_type IN( 'DEAL','VOLUME_OFFER') THEN
1274                    -- 6/13/2002 mpande added for Trade Deal Offer -- It is a combof Off invoice and Accrual
1275                       l_accrual_flag :='N';
1276                       OPEN c_accrual_flag( l_util_rec.price_adjustment_id ) ;
1277                       FETCH c_accrual_flag INTO l_accrual_flag ;
1278                       CLOSE c_accrual_flag ;
1279                       IF l_accrual_flag = 'Y' THEN
1280                          l_util_rec.utilization_type := 'ACCRUAL';
1281                          --l_util_rec.adjustment_type_id := NULL;
1282                          --l_util_rec.adjustment_type := NULL;
1283                          l_util_rec.amount_remaining := l_parent_src_tbl (i).fund_amount;
1284                       -- for off invoice part of trade deal
1285                       ELSE
1286                          l_util_rec.utilization_type := 'UTILIZED';
1287                       END IF;
1288                    ELSE
1289                       l_util_rec.utilization_type := 'UTILIZED';
1290                    END IF;
1291 
1292                 ELSE
1293                    IF l_src_fund_accrual_basis = 'SALES' THEN
1294                       l_util_rec.utilization_type := 'SALES_ACCRUAL';
1295                       --l_util_rec.amount_remaining := l_parent_src_tbl (i).fund_amount;
1296                    ELSIF l_src_fund_accrual_basis = 'CUSTOMER' THEN
1297                       l_util_rec.utilization_type := 'ACCRUAL';
1298                       l_util_rec.amount_remaining := l_parent_src_tbl (i).fund_amount;
1299                    END IF;
1300                 END IF;
1301 
1302                 -- for chargback, added on 12/23/02 by feliu and move out of fixed budget.
1303                 IF   l_util_rec.object_type = 'TP_ORDER' THEN
1304                       l_util_rec.utilization_type := 'ACCRUAL';
1305                       l_util_rec.amount_remaining := l_parent_src_tbl (i).fund_amount;
1306                       IF G_DEBUG THEN
1307                          ozf_utility_pvt.debug_message (':for charge back: ' || l_parent_src_tbl (i).fund_amount );
1308                       END IF;
1309                 END IF;
1310 
1311              END IF;
1312          END IF; -- end for utlization type = utilized
1313 
1314          --added by feliu for manual adjustment.
1315          -- 12/02/2003 yzhao: 11.5.10 chargeback
1316          IF l_util_rec.utilization_type IN ('ADJUSTMENT', 'CHARGEBACK') THEN
1317             l_util_rec.amount_remaining := l_util_rec.amount;
1318          IF G_DEBUG THEN
1319          ozf_utility_pvt.debug_message(l_full_name||' : '||'l_util_rec.amount_remaining:   '|| l_util_rec.amount_remaining);
1320          END IF;
1321       END IF;
1322 
1323       -- check that cust_account_id is populated correctly
1324       -- added by rimehrot for R12, populate site id's
1325      /*
1326       IF l_qlf_type IS NOT NULL AND l_qlf_id IS NOT NULL THEN
1327       IF l_qlf_type IN ('CUSTOMER_BILL_TO', 'SHIP_TO') THEN
1328         OPEN c_cust_account_id (l_qlf_id);
1329                 FETCH c_cust_account_id INTO l_cust_account_id, l_bill_to_site_id;
1330                 CLOSE c_cust_account_id;
1331 
1332         IF l_qlf_type = 'CUSTOMER_BILL_TO' THEN
1333           l_util_rec.bill_to_site_use_id := l_qlf_id;
1334         ELSIF l_qlf_type = 'SHIP_TO' THEN
1335           l_util_rec.bill_to_site_use_id := l_bill_to_site_id;
1336           l_util_rec.ship_to_site_use_id := l_qlf_id;
1337         END IF;
1338 
1339       END IF; -- l_qlf_type is billto/shipto
1340       END IF; --l_qlf_type not null
1341 */
1342       --kdass 02-AUG-2005 - R12 change for paid adjustments
1343       IF l_util_rec.utilization_type = 'ADJUSTMENT' AND
1344             NVL(l_util_rec.adjustment_type, ' ') IN ('INCREASE_PAID', 'DECREASE_PAID') THEN
1345             l_util_rec.amount_remaining := - l_util_rec.amount;
1346             l_util_rec.amount := 0;
1347             --kdass fixed bug 9432297
1348             l_util_rec.plan_curr_amount_remaining := - l_util_rec.plan_curr_amount;
1349             l_util_rec.plan_curr_amount := 0;
1350             l_util_rec.fund_request_amount_remaining := - l_util_rec.fund_request_amount;
1351             l_util_rec.fund_request_amount := 0;
1352 
1353             l_util_rec.gl_posted_flag := ozf_accrual_engine.G_GL_FLAG_NO;
1354       END IF;
1355 
1356 
1357       IF l_util_rec.utilization_type = 'ADJUSTMENT'
1358       THEN
1359       -- check if there is a valid budget request
1360         -- rimehrot, bug fix 4030022
1361       OPEN c_check_budget_request(l_util_rec.plan_id, l_util_rec.fund_id);
1362         FETCH c_check_budget_request INTO l_check_request;
1363           IF c_check_budget_request%ROWCOUNT = 0 THEN
1364            ozf_utility_pvt.error_message('OZF_NO_FUND_REQUEST');
1365            RAISE fnd_api.g_exc_unexpected_error;
1366          END IF;
1367           CLOSE c_check_budget_request;
1368       END IF;
1369 
1370       /*bug 8532055
1371       --nirprasa for bug 7425189, send exchange_rate_date for utilization
1372       IF p_act_budget_rec.justification IN (l_fund_reconc_msg,l_act_bud_cst_msg)
1373       AND p_act_budget_rec.exchange_rate_date IS NOT NULL THEN
1374         l_util_rec.exchange_rate_date := p_act_budget_rec.exchange_rate_date;
1375       END IF;
1376       */
1377 
1378       --bug 7425189, 8532055
1379       --introduced this condition to prevent exchange_rate_date from being overriden.
1380       --In case of volume offer adjustment,exchange_rate_date is passed from volume_offer_adjustment API in ozfvadeb.pls
1381       --ninarasi fix for bug 16029659
1382       IF l_util_rec.adjustment_type_id NOT IN (-6,-7) THEN
1383          l_util_rec.exchange_rate_date := p_act_budget_rec.exchange_rate_date;
1384       END IF;
1385 
1386       --kdass - bug 9470625
1387       l_util_rec.cost_price := p_act_util_rec.cost_price;
1388       l_util_rec.cost_price_currency_code := p_act_util_rec.cost_price_currency_code;
1389       l_util_rec.discount_type := p_act_util_rec.discount_type;
1390       l_util_rec.discount_amount := p_act_util_rec.discount_amount;
1391       l_util_rec.discount_amount_currency_code := p_act_util_rec.discount_amount_currency_code;
1392 
1393         -- For Bug#8867381, introduced p_use_fund_staging_tables for staging table impln of chargeback flow
1394         -- and px_ozf_act_budgets_tbl for PLSQL table impln of storing budgets value.
1395         -- and px_ozf_funds_old_rectype for taking the funds old values
1396 	    -- For TPA Parallel Execution ERBug#9614703
1397         -- and changed px_ozf_funds_new_rectype to px_ozf_funds_new_tbl.
1398 
1399          ozf_fund_utilized_pvt.create_utilization (
1400             p_api_version=> l_api_version
1401            ,p_init_msg_list=> fnd_api.g_false
1402            ,p_commit=> fnd_api.g_false
1403            ,p_validation_level=> fnd_api.g_valid_level_full
1404            ,x_return_status=> l_return_status
1405            ,x_msg_count=> x_msg_count
1406            ,x_msg_data=> x_msg_data
1407            ,p_utilization_rec=> l_util_rec
1408            ,x_utilization_id=> x_utilization_id --l_util_id
1409 	   ,p_batch_type	     =>    p_batch_type
1410            ,p_use_fund_staging_tables => p_use_fund_staging_tables
1411            ,px_ozf_act_budgets_tbl => px_ozf_act_budgets_tbl
1412            ,px_ozf_funds_old_rectype    =>      px_ozf_funds_old_rectype
1413            ,px_ozf_funds_new_tbl    =>      px_ozf_funds_new_tbl      --	For TPA Parallel Execution ER - 9614703
1414          );
1415 
1416          IF l_return_status = fnd_api.g_ret_sts_error THEN
1417             RAISE fnd_api.g_exc_error;
1418          ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
1419             RAISE fnd_api.g_exc_unexpected_error;
1420          END IF;
1421       END LOOP;
1422 
1423      x_utilized_amount := l_total_amount;
1424 
1425       IF G_DEBUG THEN
1426          ozf_utility_pvt.debug_message(l_full_name||' : '||'x_utilized_amount:   '|| x_utilized_amount);
1427       END IF;
1428 
1429     fnd_msg_pub.count_and_get (
1430          p_encoded=> fnd_api.g_false
1431         ,p_count=> x_msg_count
1432         ,p_data=> x_msg_data
1433     );
1434     IF G_DEBUG THEN
1435        ozf_utility_pvt.debug_message (   l_full_name
1436                                      || ': end');
1437     END IF;
1438 
1439    EXCEPTION
1440       WHEN fnd_api.g_exc_error THEN
1441          ROLLBACK TO create_utilization;
1442          x_return_status            := fnd_api.g_ret_sts_error;
1443          fnd_msg_pub.count_and_get (
1444             p_encoded=> fnd_api.g_false
1445            ,p_count=> x_msg_count
1446            ,p_data=> x_msg_data
1447          );
1448       WHEN fnd_api.g_exc_unexpected_error THEN
1449          ROLLBACK TO create_utilization;
1450          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1451          fnd_msg_pub.count_and_get (
1452             p_encoded=> fnd_api.g_false
1453            ,p_count=> x_msg_count
1454            ,p_data=> x_msg_data
1455          );
1456       WHEN OTHERS THEN
1457          ROLLBACK TO create_utilization;
1458          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1459 
1460          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1461             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1462          END IF;
1463 
1464          fnd_msg_pub.count_and_get (
1465             p_encoded=> fnd_api.g_false
1466            ,p_count=> x_msg_count
1467            ,p_data=> x_msg_data
1468          );
1469 
1470    END create_fund_utilization;
1471 
1472 
1473 
1474 ---------------------------------------------------------------------
1475 -- PROCEDURE
1476 --    Convert_Currency
1477 --
1478 -- PURPOSE
1479 --           This API will be used to convert currency for checkbook.
1480 -- PARAMETERS
1481 --                  p_from_currency  IN VARCHAR2 From currency
1482 --                  p_to_currency IN VARCHAR@  To currency
1483 --                  p_from_amount IN NUMBER    From amount
1484 -- NOTES
1485 
1486 -- HISTORY
1487 --    06/08/2001  feliu  Create.
1488 ----------------------------------------------------------------------
1489    FUNCTION convert_currency (
1490       p_from_currency   IN   VARCHAR2
1491      ,p_to_currency     IN   VARCHAR2
1492      ,p_from_amount     IN   NUMBER
1493      ,p_conv_type       IN   VARCHAR2 DEFAULT FND_API.G_MISS_CHAR --Added for bug 7030415
1494    )
1495       RETURN NUMBER IS
1496       l_conversion_type_profile   CONSTANT VARCHAR2 (30) := 'OZF_CURR_CONVERSION_TYPE';
1497       l_user_rate                 CONSTANT NUMBER        := 1; -- Currenty not used.
1498       l_max_roll_days             CONSTANT NUMBER        := -1; -- Negative so API rolls back to find the last conversion rate.
1499       l_denominator                        NUMBER; -- Not used in Marketing.
1500       l_numerator                          NUMBER; -- Not used in Marketing.
1501       l_rate                               NUMBER; -- Not used in Marketing.
1502       l_conversion_type                    VARCHAR2 (30); -- Currency conversion type; see API documention for details.
1503       l_returned_amount                    NUMBER        := 1000;
1504    BEGIN
1505       -- Get the currency conversion type from profile option
1506       --Added for bug 7030415
1507       IF p_conv_type = FND_API.G_MISS_CHAR OR p_conv_type IS NULL THEN
1508         l_conversion_type := fnd_profile.VALUE (l_conversion_type_profile);
1509       ELSE
1510         l_conversion_type := p_conv_type;
1511       END IF;
1512       -- Call the proper GL API to convert the amount.
1513       gl_currency_api.convert_closest_amount (
1514          x_from_currency=> p_from_currency
1515         ,x_to_currency=> p_to_currency
1516         ,x_conversion_date=> SYSDATE
1517         ,x_conversion_type=> l_conversion_type
1518         ,x_user_rate=> l_user_rate
1519         ,x_amount=> p_from_amount
1520         ,x_max_roll_days=> l_max_roll_days
1521         ,x_converted_amount=> l_returned_amount
1522         ,x_denominator=> l_denominator
1523         ,x_numerator=> l_numerator
1524         ,x_rate=> l_rate
1525       );
1526       RETURN l_returned_amount;
1527    EXCEPTION
1528       WHEN gl_currency_api.no_rate THEN
1529          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1530             fnd_message.set_name ('OZF', 'OZF_NO_RATE');
1531             fnd_message.set_token ('CURRENCY_FROM', p_from_currency);
1532             fnd_message.set_token ('CURRENCY_TO', p_to_currency);
1533             fnd_msg_pub.ADD;
1534             RETURN 0;
1535          END IF;
1536       WHEN gl_currency_api.invalid_currency THEN
1537          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
1538             fnd_message.set_name ('OZF', 'OZF_INVALID_CURR');
1539             fnd_message.set_token ('CURRENCY_FROM', p_from_currency);
1540             fnd_message.set_token ('CURRENCY_TO', p_to_currency);
1541             fnd_msg_pub.ADD;
1542             RETURN 0;
1543          END IF;
1544       WHEN OTHERS THEN
1545          RETURN 0;
1546    END convert_currency;
1547 
1548 
1549 ---------------------------------------------------------------------
1550 -- PROCEDURE
1551 --    validate_lumsum_offer
1552 --
1553 -- PURPOSE
1554 --
1555 -- PARAMETERS
1556    --p_qp_list_header_id     IN   NUMBER
1557    --x_return_status         OUT NOCOPY  VARCHAR2);
1558 -- NOTES
1559 --        This API will validate the lumsum offer distribution
1560 -- HISTORY
1561 --   09/24/2001  Mumu Pande  Create.
1562 ----------------------------------------------------------------------
1563 
1564    PROCEDURE validate_lumpsum_offer (p_qp_list_header_id IN NUMBER, x_return_status OUT NOCOPY VARCHAR2) IS
1565       l_api_version   CONSTANT NUMBER                            := 1.0;
1566       l_api_name      CONSTANT VARCHAR2 (30)                     := 'validate_lumpsum_offer';
1567       l_full_name     CONSTANT VARCHAR2 (60)                     :=    g_pkg_name
1568                                                                     || '.'
1569                                                                     || l_api_name;
1570 
1571       CURSOR cur_get_lumpsum_details IS
1572          SELECT status_code
1573                ,lumpsum_amount
1574                ,object_version_number
1575                ,distribution_type
1576                ,qp_list_header_id
1577                ,offer_id
1578            FROM ozf_offers
1579           WHERE qp_list_header_id = p_qp_list_header_id;
1580 
1581       l_lumpsum_offer          cur_get_lumpsum_details%ROWTYPE;
1582 
1583       CURSOR cur_get_lumpsum_line_details IS
1584          SELECT SUM (line_lumpsum_qty)
1585            FROM ams_act_products
1586           WHERE arc_act_product_used_by = 'OFFR'
1587             AND act_product_used_by_id = p_qp_list_header_id;
1588 
1589       l_total_distribution     NUMBER;
1590 
1591       CURSOR c_approved_amount (p_offer_id NUMBER) IS
1592          SELECT SUM(NVL(plan_curr_committed_amt,0))
1593          FROM ozf_object_fund_summary
1594          WHERE object_id =p_offer_id
1595          AND object_type = 'OFFR';
1596 
1597          /* Fix for the bug#3047142
1598          SELECT SUM(DECODE(transfer_type,'REQUEST', NVL(approved_amount,0),NVL(0-approved_original_amount,0)))
1599          FROM ozf_act_budgets
1600          WHERE status_code = 'APPROVED'
1601          AND ((arc_act_budget_used_by = 'OFFR' AND act_budget_used_by_id = l_id and transfer_type ='REQUEST')
1602               OR (budget_source_type = 'OFFR' AND budget_source_id = l_id and transfer_type ='TRANSFER'));
1603 
1604          /* SELECT SUM(DECODE(transfer_type,'REQUEST', NVL(approved_amount,0),NVL(0-approved_original_amount,0)))
1605            FROM ozf_act_budgets
1606           WHERE arc_act_budget_used_by = 'OFFR'
1607             AND act_budget_used_by_id = l_id;
1608      */
1609 
1610       l_approved_amount        NUMBER;
1611    BEGIN
1612       x_return_status            := fnd_api.g_ret_sts_success;
1613       OPEN cur_get_lumpsum_details;
1614       FETCH cur_get_lumpsum_details INTO l_lumpsum_offer;
1615       CLOSE cur_get_lumpsum_details;
1616       OPEN cur_get_lumpsum_line_details;
1617       FETCH cur_get_lumpsum_line_details INTO l_total_distribution;
1618       CLOSE cur_get_lumpsum_line_details;
1619       OPEN c_approved_amount (p_qp_list_header_id);
1620       FETCH c_approved_amount INTO l_approved_amount;
1621       CLOSE c_approved_amount;
1622 
1623       --nirprasa, comment out for bug 8625525
1624      /*  IF l_lumpsum_offer.lumpsum_amount > l_approved_amount
1625          OR l_lumpsum_offer.lumpsum_amount < l_approved_amount THEN
1626          ozf_utility_pvt.error_message (p_message_name => 'OZF_OFFER_AMNT_GT_APPR_AMNT');
1627          RAISE fnd_api.g_exc_error;
1628       END IF;*/
1629 
1630       IF l_lumpsum_offer.distribution_type = 'AMT' THEN
1631          IF l_total_distribution <> l_lumpsum_offer.lumpsum_amount THEN
1632             fnd_message.set_name ('OZF', 'OZF_INVALID_DISTR_ACTIVE');
1633             fnd_msg_pub.ADD;
1634             RAISE fnd_api.g_exc_error;
1635          ELSIF l_total_distribution > l_lumpsum_offer.lumpsum_amount THEN
1636             fnd_message.set_name ('OZF', 'OZF_INVALID_DISTRIBUTION');
1637             fnd_msg_pub.ADD;
1638             RAISE fnd_api.g_exc_error;
1639          END IF;
1640       ELSIF l_lumpsum_offer.distribution_type = '%' THEN
1641          IF l_total_distribution <> 100 THEN
1642             fnd_message.set_name ('OZF', 'OZF_INVALID_DISTR_ACTIVE');
1643             fnd_msg_pub.ADD;
1644             RAISE fnd_api.g_exc_error;
1645          ELSIF l_total_distribution > 100 THEN
1646             fnd_message.set_name ('OZF', 'OZF_INVALID_DISTRIBUTION');
1647             fnd_msg_pub.ADD;
1648             RAISE fnd_api.g_exc_error;
1649          END IF;
1650       END IF;
1651    EXCEPTION
1652       WHEN fnd_api.g_exc_error THEN
1653          x_return_status            := fnd_api.g_ret_sts_error;
1654       WHEN OTHERS THEN
1655          x_return_status            := fnd_api.g_ret_sts_unexp_error;
1656 
1657          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1658             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
1659          END IF;
1660    END validate_lumpsum_offer;
1661   ---------------------------------------------------------------------
1662    -- PROCEDURE
1663    --    get_exchange_rate
1664    -- PURPOSE
1665    -- Get currency exchange rate. called by BudgetOverVO.java.
1666    -- PARAMETERS
1667    --         p_from_currency   IN VARCHAR2,
1668    --           p_to_currency   IN VARCHAR2,
1669    --           p_conversion_date IN DATE ,
1670    --           p_conversion_type IN VARCHAR2,
1671    --           p_max_roll_days  IN NUMBER,
1672    --           x_denominator   OUT NUMBER,
1673    --       x_numerator OUT NUMBER,
1674    --           x_rate    OUT NUMBER,
1675    --           x_return_status   OUT  VARCHAR2
1676 
1677    -- HISTORY
1678    -- 02/05/2002 feliu  CREATED
1679    ----------------------------------------------------------------------
1680    PROCEDURE get_exchange_rate (
1681         p_from_currency IN VARCHAR2,
1682         p_to_currency   IN VARCHAR2,
1683         p_conversion_date IN DATE ,
1684         p_conversion_type IN VARCHAR2,
1685         p_max_roll_days  IN NUMBER,
1686         x_denominator   OUT NOCOPY NUMBER,
1687         x_numerator     OUT NOCOPY NUMBER,
1688         x_rate    OUT NOCOPY NUMBER,
1689         x_return_status  OUT NOCOPY  VARCHAR2)
1690 
1691 IS
1692 
1693 BEGIN
1694    gl_currency_api.get_closest_triangulation_rate (
1695                 x_from_currency =>      p_from_currency,
1696                 x_to_currency   =>      p_to_currency,
1697                 x_conversion_date =>     p_conversion_date,
1698                 x_conversion_type =>    p_conversion_type,
1699                 x_max_roll_days   =>     p_max_roll_days,
1700                 x_denominator   => x_denominator,
1701                 x_numerator     => x_numerator,
1702                 x_rate    => x_rate );
1703 
1704    x_return_status := fnd_api.g_ret_sts_success;
1705 
1706    EXCEPTION
1707       WHEN OTHERS THEN
1708          IF SQLCODE=1  THEN
1709             x_denominator := 1.0;
1710             x_numerator := 0.0;
1711             x_rate := 1.0;
1712             x_return_status := FND_API.g_ret_sts_success;
1713          END IF;
1714 END get_exchange_rate;
1715 
1716 
1717       ---------------------------------------------------------------------
1718    -- PROCEDURE
1719    --    process_act_budgets
1720    --
1721    -- PURPOSE
1722    --
1723    -- PARAMETERS
1724    --         p_api_version
1725    --         ,x_return_status
1726 --            ,x_msg_count
1727 --            ,x_msg_data
1728   --          ,p_act_budgets_rec
1729     --        ,x_act_budget_id
1730     --        x_utilized_amount : actual utilized amount when success
1731    --         p_use_fund_staging_tables for staging table impln of chargeback flow (For Bug#8867381)
1732    --         px_ozf_act_budgets_tbl for PLSQL table impln of storing budgets value.
1733    --         px_ozf_funds_old_rectype for taking the funds old values
1734    --         px_ozf_funds_new_tbl for taking the new values after updation.  (For TPA Parallel Execution ER Bug#9614703)
1735    -- NOTES
1736    -- HISTORY
1737    --    4/18/2002  Mumu Pande  Create.
1738    ----------------------------------------------------------------------
1739 
1740    PROCEDURE process_act_budgets (
1741       x_return_status     OUT NOCOPY      VARCHAR2,
1742       x_msg_count         OUT NOCOPY      NUMBER,
1743       x_msg_data          OUT NOCOPY      VARCHAR2,
1744       p_act_budgets_rec   IN  ozf_actbudgets_pvt.act_budgets_rec_type,
1745       p_act_util_rec      IN  ozf_actbudgets_pvt.act_util_rec_type,
1746       x_act_budget_id     OUT NOCOPY      NUMBER,
1747       x_utilized_amount   OUT NOCOPY      NUMBER,                 -- added yzhao Jun 21, 2004
1748       p_batch_type	     IN  VARCHAR2,
1749       p_use_fund_staging_tables IN        VARCHAR2,
1750       px_ozf_act_budgets_tbl    IN OUT NOCOPY OZF_UTILITY_PVT.ozf_act_budgets_table,
1751       px_ozf_funds_old_rectype  IN      OZF_UTILITY_PVT.ozf_funds_all_b_rectype,
1752       px_ozf_funds_new_tbl  IN OUT NOCOPY   OZF_UTILITY_PVT.ozf_funds_table
1753    ) IS
1754      l_utilization_id        NUMBER;
1755    BEGIN
1756 
1757       --kdass - added for Bug 8726683
1758       process_act_budgets (
1759          x_return_status   => x_return_status
1760         ,x_msg_count       => x_msg_count
1761         ,x_msg_data        => x_msg_data
1762         ,p_act_budgets_rec => p_act_budgets_rec
1763         ,p_act_util_rec    => p_act_util_rec
1764         ,x_act_budget_id   => x_act_budget_id
1765         ,x_utilized_amount => x_utilized_amount
1766 	,p_batch_type	     =>    p_batch_type
1767         ,p_use_fund_staging_tables => p_use_fund_staging_tables
1768         ,px_ozf_act_budgets_tbl    => px_ozf_act_budgets_tbl
1769         ,px_ozf_funds_old_rectype  => px_ozf_funds_old_rectype
1770         ,px_ozf_funds_new_tbl  => px_ozf_funds_new_tbl
1771         ,x_utilization_id  => l_utilization_id);
1772 
1773    END process_act_budgets;
1774 
1775    PROCEDURE process_act_budgets (
1776       x_return_status     OUT NOCOPY      VARCHAR2,
1777       x_msg_count         OUT NOCOPY      NUMBER,
1778       x_msg_data          OUT NOCOPY      VARCHAR2,
1779       p_act_budgets_rec   IN  ozf_actbudgets_pvt.act_budgets_rec_type,
1780       p_act_util_rec      IN  ozf_actbudgets_pvt.act_util_rec_type,
1781       x_act_budget_id     OUT NOCOPY      NUMBER,
1782       x_utilized_amount   OUT NOCOPY      NUMBER,                -- added yzhao Jun 21, 2004
1783       p_batch_type	     IN  VARCHAR2,
1784       p_use_fund_staging_tables IN        VARCHAR2,
1785       px_ozf_act_budgets_tbl    IN OUT NOCOPY OZF_UTILITY_PVT.ozf_act_budgets_table,
1786       px_ozf_funds_old_rectype  IN      OZF_UTILITY_PVT.ozf_funds_all_b_rectype,
1787       px_ozf_funds_new_tbl  IN OUT NOCOPY   OZF_UTILITY_PVT.ozf_funds_table,
1788       x_utilization_id    OUT NOCOPY      NUMBER
1789    ) IS
1790       CURSOR c_act_util_rec (p_used_by_id IN NUMBER, p_used_by_type IN VARCHAR2) IS
1791          SELECT activity_budget_id, object_version_number, approved_amount
1792          FROM ozf_act_budgets
1793          WHERE act_budget_used_by_id = p_used_by_id
1794          AND arc_act_budget_used_by = p_used_by_type
1795          AND transfer_type = 'UTILIZED';
1796       CURSOR c_offer_type (p_offer_id IN NUMBER) IS
1797          SELECT nvl(transaction_currency_code,fund_request_curr_code) offer_currency_code
1798          FROM   ozf_offers
1799          WHERE  qp_list_header_id = p_offer_id;
1800       CURSOR c_get_conversion_type( p_org_id IN NUMBER) IS
1801          SELECT exchange_rate_type
1802          FROM   ozf_sys_parameters_all
1803          WHERE  org_id = p_org_id;
1804 
1805       l_activity_id           NUMBER;
1806       l_obj_ver_num           NUMBER;
1807       l_old_approved_amount   NUMBER;
1808       --l_return_status         VARCHAR2 (20);
1809       l_api_name              VARCHAR2 (60)         := 'process_act_budget';
1810       l_full_name             VARCHAR2 (100)         := g_pkg_name||'.'||l_api_name;
1811       l_act_budget_id         NUMBER;
1812       l_utilized_amount    NUMBER;
1813       l_act_budgets_rec       ozf_actbudgets_pvt.act_budgets_rec_type:=p_Act_budgets_rec;
1814       l_old_act_budgets_rec   ozf_actbudgets_pvt.act_budgets_rec_type;
1815       l_act_util_rec          ozf_actbudgets_pvt.act_util_rec_type := p_act_util_rec;
1816       l_api_version           NUMBER                                  := 1;
1817       l_budget_request_rec    ozf_actbudgets_pvt.act_budgets_rec_type := NULL;
1818       l_plan_currency         VARCHAR2(150);
1819       l_exchange_rate_type    VARCHAR2(30) := FND_API.G_MISS_CHAR ;
1820       l_rate                  NUMBER;
1821       --l_utilized_amount       NUMBER;
1822         -- For Bug#8867381
1823       l_activity_budget_id NUMBER;
1824       l_request_amount NUMBER;
1825       l_approved_amount NUMBER;
1826       l_approved_original_amount NUMBER;
1827       l_approved_amount_fc NUMBER;
1828       l_parent_src_apprvd_amt NUMBER;
1829       l_src_curr_request_amt NUMBER;
1830 
1831 
1832         -- For Bug#8867381
1833       CURSOR old_budgets_csr(p_act_budget_id IN NUMBER) IS
1834       SELECT REQUEST_AMOUNT, APPROVED_AMOUNT, APPROVED_ORIGINAL_AMOUNT, APPROVED_AMOUNT_FC,
1835       PARENT_SRC_APPRVD_AMT, SRC_CURR_REQUEST_AMT FROM OZF_ACT_BUDGETS
1836       WHERE ACTIVITY_BUDGET_ID = p_act_budget_id;
1837 
1838    BEGIN
1839       x_return_status := fnd_api.g_ret_sts_success;
1840       IF G_DEBUG THEN
1841          ozf_utility_pvt.debug_message(l_full_name||' : '||'begin' || ' p_act_budgets_rec.transfer_type: '  || p_act_budgets_rec.transfer_type);
1842       END IF;
1843 
1844        ozf_utility_pvt.debug_message(' p_act_util_rec.plan_currency_code mg: '  || p_act_util_rec.plan_currency_code);
1845       --dbms_output.put_line(l_full_name||' : '||'begin');
1846 
1847       -- yzhao: 10/21/2003 for third party accrual price list, create an approved budget request when accrual happens
1848       --                   note: Price list does not allow negative accrual for now
1849       IF (p_act_budgets_rec.transfer_type = 'UTILIZED' AND
1850           p_act_budgets_rec.budget_source_type = 'PRIC' AND
1851           p_act_budgets_rec.arc_act_budget_used_by = 'PRIC' AND
1852           p_act_budgets_rec.status_code = 'APPROVED' AND
1853           p_act_budgets_rec.request_amount > 0) THEN
1854 
1855           l_budget_request_rec.transfer_type := 'REQUEST';
1856           l_budget_request_rec.budget_source_type := 'FUND';
1857           l_budget_request_rec.budget_source_id := p_act_budgets_rec.parent_source_id;  -- passed by price list from its profile
1858           l_budget_request_rec.arc_act_budget_used_by := 'PRIC';
1859           l_budget_request_rec.act_budget_used_by_id := p_act_budgets_rec.act_budget_used_by_id;
1860           l_budget_request_rec.request_currency := p_act_budgets_rec.request_currency;  -- price list currency
1861           l_budget_request_rec.request_amount := p_act_budgets_rec.request_amount;      -- in price list currency
1862 
1863           l_budget_request_rec.status_code := 'APPROVED';
1864           l_budget_request_rec.user_status_id := ozf_Utility_Pvt.get_default_user_status (
1865                                                     'OZF_BUDGETSOURCE_STATUS', p_act_budgets_rec.status_code);
1866           l_budget_request_rec.object_version_number := 1;
1867           l_budget_request_rec.approval_date := sysdate;
1868           --l_budget_request_rec.approver_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
1869           --l_budget_request_rec.requester_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
1870           l_budget_request_rec.approver_id := p_act_budgets_rec.approver_id;
1871           l_budget_request_rec.requester_id := p_act_budgets_rec.requester_id;
1872           IF l_budget_request_rec.approver_id  IS NULL THEN
1873              l_budget_request_rec.approver_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
1874           END IF;
1875           IF l_budget_request_rec.requester_id  IS NULL THEN
1876              l_budget_request_rec.requester_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
1877           END IF;
1878 
1879         -- For Bug#8867381, introduced p_use_fund_staging_tables for staging table impln of chargeback flow
1880         -- and px_ozf_act_budgets_tbl for PLSQL table impln of storing budgets value.
1881         -- and px_ozf_funds_old_rectype for taking the funds old values
1882 	    -- For TPA Parallel Execution ERBug#9614703
1883         -- and changed px_ozf_funds_new_rectype to px_ozf_funds_new_tbl.
1884 
1885           ozf_actbudgets_pvt.create_Act_Budgets (
1886                              p_api_version             => 1.0,
1887                              p_init_msg_list           => Fnd_Api.G_FALSE,
1888                              p_commit                  => Fnd_Api.G_FALSE,
1889                              p_validation_level        => Fnd_Api.G_VALID_LEVEL_FULL,
1890                              x_return_status           => x_return_status,
1891                              x_msg_count               => x_msg_count,
1892                              x_msg_data                => x_msg_data,
1893                              p_act_Budgets_rec         => l_budget_request_rec,
1894                              p_act_util_rec            => ozf_actbudgets_pvt.G_MISS_ACT_UTIL_REC,
1895                              p_approval_flag           => fnd_api.g_true,     -- auto approved
1896                              x_act_budget_id           => l_act_budget_id,
1897                              x_utilized_amount         => l_utilized_amount,
1898                              p_resale_batch_id         => l_act_util_rec.reference_id,
1899 			     p_batch_type	     =>    p_batch_type,
1900                              p_use_fund_staging_tables => p_use_fund_staging_tables,
1901                              px_ozf_act_budgets_tbl => px_ozf_act_budgets_tbl,
1902                              px_ozf_funds_old_rectype   =>      px_ozf_funds_old_rectype,
1903                              px_ozf_funds_new_tbl     =>      px_ozf_funds_new_tbl,  -- For TPA Parallel Execution ERBug#9614703
1904                              x_utilization_id          => x_utilization_id);  --nirprasa - added for Bug 9383565
1905 
1906 
1907           IF x_return_status <> fnd_api.g_ret_sts_success THEN
1908              RAISE fnd_api.g_exc_unexpected_error;
1909           END IF;
1910 
1911       END IF;  -- price list
1912       -- yzhao: 10/21/2003 ENDS for third party accrual price list, create an approved budget request when accrual happens
1913 
1914       OPEN c_act_util_rec (
1915          p_act_budgets_rec.act_budget_used_by_id,
1916          p_act_budgets_rec.arc_act_budget_used_by
1917       );
1918       FETCH c_act_util_rec INTO l_activity_id,
1919                                 l_obj_ver_num,
1920                                 l_old_approved_amount;
1921       CLOSE c_act_util_rec;
1922 
1923       --nirprasa, added for bug 9097346. since post multi currency changes need to populate
1924       --these new columns for marketing objects
1925 
1926        ozf_utility_pvt.debug_message(' l_act_util_rec.plan_curr_amount mg: '  || l_act_util_rec.plan_curr_amount);
1927        ozf_utility_pvt.debug_message(' l_act_util_rec.plan_currency_code mg: '  || l_act_util_rec.plan_currency_code);
1928        ozf_utility_pvt.debug_message(' l_act_budgets_rec.arc_act_budget_used_by mg: '  || l_act_budgets_rec.arc_act_budget_used_by);
1929 
1930 
1931       IF l_act_budgets_rec.arc_act_budget_used_by <> 'OFFR' THEN
1932           l_act_util_rec.plan_curr_amount := l_act_budgets_rec.request_amount;
1933           l_act_util_rec.fund_request_currency_code  := l_act_budgets_rec.request_currency;
1934           l_act_util_rec.plan_currency_code := l_act_budgets_rec.request_currency;
1935       END IF;
1936 
1937       --dbms_output.put_line(l_full_name||' : '||'l_Activity_budget_id'|| l_Activity_id);
1938 
1939       IF l_activity_id IS NULL THEN
1940          --l_act_budgets_rec.approved_amount := l_util_amount;
1941          --l_act_budgets_rec.parent_src_apprvd_amt := l_parent_source_rec.total_amount;
1942          /*ozf_actbudgets_pvt.create_act_budgets (
1943             p_api_version=> l_api_version,
1944             x_return_status=> x_return_status,
1945             x_msg_count=> x_msg_count,
1946             x_msg_data=> x_msg_data,
1947             p_act_budgets_rec=> l_act_budgets_rec,
1948             x_act_budget_id=> l_act_budget_id,
1949             p_act_util_rec => l_act_util_rec,
1950             x_utilized_amount => x_utilized_amount,    -- yzhao: 06/21/2004 added for chargeback
1951             x_utilization_id          => x_utilization_id  --nirprasa - added for Bug 9383565
1952          );*/
1953          /* Bug#9614703 update to ozf_funds_all_tl table was happening during creation of act_budget
1954              records. So we need to send p_use_fund_staging_tables flag and px_ozf_act_budgets_tbl rec
1955              in this flow as well. Hence used the overloaded procedure.
1956          */
1957          ozf_actbudgets_pvt.create_act_budgets (
1958             p_api_version=> l_api_version,
1959             p_init_msg_list           => Fnd_Api.G_FALSE,
1960             p_commit                  => Fnd_Api.G_FALSE,
1961             p_validation_level        => Fnd_Api.G_VALID_LEVEL_FULL,
1962             x_return_status=> x_return_status,
1963             x_msg_count=> x_msg_count,
1964             x_msg_data=> x_msg_data,
1965             p_act_budgets_rec=> l_act_budgets_rec,
1966             p_act_util_rec            => l_act_util_rec,
1967             p_approval_flag           => fnd_api.g_true,     -- auto approved
1968             x_act_budget_id=> l_act_budget_id,
1969             x_utilized_amount => x_utilized_amount,     -- yzhao: 06/21/2004 added for chargeback
1970             p_resale_batch_id         => l_act_util_rec.reference_id,
1971             p_batch_type             =>    p_batch_type,
1972             p_use_fund_staging_tables => p_use_fund_staging_tables,
1973             px_ozf_act_budgets_tbl => px_ozf_act_budgets_tbl,
1974             px_ozf_funds_old_rectype   =>      px_ozf_funds_old_rectype,
1975             px_ozf_funds_new_tbl     =>      px_ozf_funds_new_tbl,
1976             x_utilization_id          => x_utilization_id  --nirprasa - added for Bug 9383565
1977          );
1978 
1979             IF G_DEBUG THEN
1980          ozf_utility_pvt.write_conc_log(l_full_name||' : '||'tim 4:   '|| x_utilized_amount);
1981       END IF;
1982 
1983       IF G_DEBUG THEN
1984          ozf_utility_pvt.write_conc_log(l_full_name||' : '||'create act budget retrun status'||x_return_status);
1985       END IF;
1986       --dbms_output.put_line(l_full_name||' : '||'create act budget retrun status'||l_return_status);
1987 
1988          IF x_return_status = fnd_api.g_ret_sts_error THEN
1989             RAISE fnd_api.g_exc_error;
1990          ELSIF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
1991             RAISE fnd_api.g_exc_unexpected_error;
1992          END IF;
1993       ELSE
1994       --dbms_output.put_line(l_full_name||' : '||'l_Activity_budget_id in update'||l_Activity_id);
1995       --dbms_output.put_line(l_full_name||' : '||'l_old_approved_amount'||l_old_approved_amount);
1996       --dbms_output.put_line(l_full_name||' : '||'l_new approved_amount'||l_Act_budgets_rec.approved_amount);
1997       --dbms_output.put_line(l_full_name||' : '||'l_new parent approved_amount'||l_act_budgets_rec.parent_src_apprvd_amt);
1998       IF G_DEBUG THEN
1999       ozf_utility_pvt.debug_message('l_act_budgets_rec.request_amount '|| l_act_budgets_rec.request_amount);
2000       ozf_utility_pvt.debug_message('l_act_budgets_rec.request_currency '|| l_act_budgets_rec.request_currency);
2001       ozf_utility_pvt.debug_message('l_old_approved_amount '|| l_old_approved_amount);
2002       ozf_utility_pvt.debug_message('l_act_budgets_rec.parent_src_apprvd_amt '|| l_act_budgets_rec.parent_src_apprvd_amt);
2003       ozf_utility_pvt.debug_message('l_act_budgets_rec.arc_act_budget_used_by '|| l_act_budgets_rec.arc_act_budget_used_by);
2004       END IF;
2005       --nirprasa, 12.2 ER8399134 this change is needed to handle adjustments for marketing objects.
2006       IF l_act_budgets_rec.arc_act_budget_used_by = 'OFFR' THEN
2007          OPEN c_offer_type(l_act_budgets_rec.act_budget_used_by_id);
2008          FETCH c_offer_type INTO l_plan_currency;
2009          CLOSE c_offer_type;
2010 
2011          IF l_plan_currency <> l_act_budgets_rec.request_currency THEN
2012             OPEN c_get_conversion_type(l_act_util_rec.org_id);
2013             FETCH c_get_conversion_type INTO l_exchange_rate_type;
2014             CLOSE c_get_conversion_type;
2015             IF G_DEBUG THEN
2016             ozf_utility_pvt.debug_message('l_plan_currency '|| l_plan_currency);
2017             ozf_utility_pvt.debug_message('l_exchange_rate_type '|| l_exchange_rate_type);
2018             END IF;
2019             l_act_util_rec.plan_curr_amount := l_act_budgets_rec.request_amount;
2020             l_act_util_rec.plan_curr_amount_remaining := l_act_budgets_rec.request_amount;
2021             l_act_util_rec.plan_currency_code := l_act_budgets_rec.request_currency;
2022             ozf_utility_pvt.convert_currency (x_return_status => x_return_status
2023                                       ,p_from_currency => l_act_budgets_rec.request_currency
2024                                       ,p_to_currency   => l_plan_currency
2025                                       ,p_conv_type     => l_exchange_rate_type -- Added for bug 7030415
2026                                       ,p_from_amount   => l_act_budgets_rec.request_amount
2027                                       ,x_to_amount     => l_act_budgets_rec.approved_amount
2028                                       ,x_rate          => l_rate
2029                                       );
2030             l_act_budgets_rec.request_amount := l_act_budgets_rec.approved_amount;
2031             l_act_budgets_rec.approved_original_amount := l_act_budgets_rec.approved_amount;
2032             l_act_budgets_rec.request_currency := l_plan_currency;
2033             IF G_DEBUG THEN
2034             ozf_utility_pvt.debug_message('l_act_budgets_rec.request_amount '|| l_act_budgets_rec.request_amount);
2035             END IF;
2036          END IF;
2037 
2038       ELSE --for marketing objects
2039          l_act_util_rec.plan_curr_amount := l_act_budgets_rec.request_amount;
2040          l_act_util_rec.plan_currency_code := l_act_budgets_rec.request_currency;
2041          l_act_util_rec.fund_request_currency_code  := l_act_budgets_rec.request_currency;
2042       END IF;
2043          l_act_budgets_rec.request_amount :=
2044                       l_old_approved_amount
2045                     + l_act_budgets_rec.request_amount;
2046 
2047           l_act_budgets_rec.approved_amount :=
2048                       l_old_approved_amount
2049                     + l_act_budgets_rec.request_amount;
2050 
2051 
2052          l_act_budgets_rec.parent_src_apprvd_amt :=
2053                  l_act_budgets_rec.parent_src_apprvd_amt;
2054          l_act_budgets_rec.activity_budget_id := l_activity_id;
2055          l_act_budgets_rec.object_version_number := l_obj_ver_num;
2056 
2057 
2058         OPEN old_budgets_csr(l_activity_id);
2059         FETCH old_budgets_csr INTO  l_request_amount, l_approved_amount, l_approved_original_amount, l_approved_amount_fc,
2060         l_parent_src_apprvd_amt, l_src_curr_request_amt;
2061         CLOSE old_budgets_csr;
2062 
2063         l_old_act_budgets_rec.request_amount            := l_request_amount;
2064         l_old_act_budgets_rec.approved_amount           := l_approved_amount;
2065         l_old_act_budgets_rec.approved_original_amount  := l_approved_original_amount;
2066         l_old_act_budgets_rec.approved_amount_fc        := l_approved_amount_fc;
2067         l_old_act_budgets_rec.parent_src_apprvd_amt     := l_parent_src_apprvd_amt;
2068         l_old_act_budgets_rec.src_curr_request_amt      := l_src_curr_request_amt;
2069 
2070 /*
2071          ozf_actbudgets_pvt.update_act_budgets (
2072             p_api_version=> l_api_version,
2073             x_return_status=> x_return_status,
2074             x_msg_count=> x_msg_count,
2075             x_msg_data=> x_msg_data,
2076             p_act_budgets_rec=> l_act_budgets_rec,
2077             p_child_approval_flag    => 'N'             ,
2078             p_act_util_rec => l_act_util_rec,
2079             x_utilized_amount => x_utilized_amount     -- yzhao: 06/21/2004 added for chargeback
2080          );
2081 */
2082 
2083         -- For Bug#8867381, introduced p_use_fund_staging_tables for staging table impln of chargeback flow
2084         -- and px_ozf_act_budgets_tbl for PLSQL table impln of storing budgets value.
2085         -- and px_ozf_funds_old_rectype for taking the funds old values
2086 	-- For TPA Parallel Execution ERBug#9614703
2087         -- and changed px_ozf_funds_new_rectype to px_ozf_funds_new_tbl.
2088 
2089 
2090 
2091          ozf_actbudgets_pvt.update_act_budgets (
2092             p_api_version=> l_api_version,
2093             x_return_status=> x_return_status,
2094             x_msg_count=> x_msg_count,
2095             x_msg_data=> x_msg_data,
2096             p_old_act_budgets_rec => l_old_act_budgets_rec,
2097             p_act_budgets_rec=> l_act_budgets_rec,
2098             p_parent_process_flag=> fnd_api.g_false,
2099             p_parent_process_key=> fnd_api.g_miss_char,
2100             p_parent_context=> fnd_api.g_miss_char,
2101             p_parent_approval_flag=> fnd_api.g_false,
2102             p_continue_flow=> fnd_api.g_false,
2103             p_child_approval_flag    => 'N',
2104             p_requestor_owner_flag   => 'N',
2105             p_act_util_rec => l_act_util_rec,
2106             x_utilized_amount => x_utilized_amount,
2107 	    p_batch_type	     =>    p_batch_type,
2108             p_use_fund_staging_tables => p_use_fund_staging_tables,
2109             px_ozf_act_budgets_tbl => px_ozf_act_budgets_tbl,
2110             px_ozf_funds_old_rectype    =>      px_ozf_funds_old_rectype,
2111             px_ozf_funds_new_tbl     =>      px_ozf_funds_new_tbl,  -- For TPA Parallel Execution ERBug#9614703
2112             x_utilization_id          => x_utilization_id  --nirprasa - added for Bug 9383565
2113          );
2114 
2115 
2116       IF G_DEBUG THEN
2117          ozf_utility_pvt.debug_message(l_full_name||' : '||'update act budget retrun status'||x_return_status);
2118       END IF;
2119       --dbms_output.put_line(l_full_name||' : '||'update act budget retrun status'||l_return_status);
2120 
2121       END IF;
2122 
2123          fnd_msg_pub.count_and_get (
2124             p_count=> x_msg_count,
2125             p_data=> x_msg_data,
2126             p_encoded=> fnd_api.g_false
2127          );
2128 
2129       IF x_return_status = fnd_api.g_ret_sts_error THEN
2130          RAISE fnd_api.g_exc_error;
2131       ELSIF x_return_status = fnd_api.g_ret_sts_unexp_error THEN
2132          RAISE fnd_api.g_exc_unexpected_error;
2133       END IF;
2134 
2135    EXCEPTION
2136       WHEN fnd_api.g_exc_error THEN
2137          x_return_status := fnd_api.g_ret_sts_error;
2138          fnd_msg_pub.count_and_get (
2139             p_count=> x_msg_count,
2140             p_data=> x_msg_data,
2141             p_encoded=> fnd_api.g_false
2142          );
2143       WHEN fnd_api.g_exc_unexpected_error THEN
2144          x_return_status := fnd_api.g_ret_sts_unexp_error;
2145          fnd_msg_pub.count_and_get (
2146             p_count=> x_msg_count,
2147             p_data=> x_msg_data,
2148             p_encoded=> fnd_api.g_false
2149          );
2150       WHEN OTHERS THEN
2151          x_return_status := fnd_api.g_ret_sts_unexp_error;
2152 
2153          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2154             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
2155          END IF;
2156 
2157          fnd_msg_pub.count_and_get (
2158             p_count=> x_msg_count,
2159             p_data=> x_msg_data,
2160             p_encoded=> fnd_api.g_false
2161          );
2162    END process_act_budgets;
2163 
2164 
2165    ---------------------------------------------------------------------
2166    -- PROCEDURE
2167    --    process_act_budgets
2168    --
2169    -- PURPOSE
2170    --    overloaded to return actual utilized amount
2171    --
2172    -- PARAMETERS
2173    --         p_api_version
2174    --         ,x_return_status
2175    --         ,x_msg_count
2176    --         ,x_msg_data
2177    --         ,p_act_budgets_rec
2178     --        ,x_act_budget_id
2179    -- NOTES
2180    -- HISTORY
2181    --    6/21/2004  Ying Zhao  Create.
2182    ----------------------------------------------------------------------
2183    PROCEDURE process_act_budgets (
2184       x_return_status     OUT NOCOPY      VARCHAR2,
2185       x_msg_count         OUT NOCOPY      NUMBER,
2186       x_msg_data          OUT NOCOPY      VARCHAR2,
2187       p_act_budgets_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type,
2188       p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type,
2189       x_act_budget_id     OUT NOCOPY      NUMBER
2190    ) IS
2191       l_utilized_amount   NUMBER;
2192    BEGIN
2193       process_act_budgets (
2194           x_return_status     => x_return_status,
2195           x_msg_count         => x_msg_count,
2196           x_msg_data          => x_msg_data,
2197           p_act_budgets_rec   => p_act_budgets_rec,
2198           p_act_util_rec      => p_act_util_rec,
2199           x_act_budget_id     => x_act_budget_id,
2200           x_utilized_amount   => l_utilized_amount
2201       );
2202    END process_act_budgets;
2203 
2204 
2205 ---------------------------------------------------------------------
2206 -- PROCEDURE
2207    --    process_act_budgets
2208    --
2209    -- PURPOSE
2210    --    overloaded to return actual utilized amount
2211    --
2212    -- PARAMETERS
2213    --         p_api_version
2214    --         ,x_return_status
2215    --            ,x_msg_count
2216    --            ,x_msg_data
2217    --          ,p_act_budgets_rec
2218     --        ,x_act_budget_id
2219    -- NOTES
2220    -- HISTORY
2221    --    6/21/2004  Ying Zhao  Create.
2222    --   12/29/2010  muthsubr   For TPA Parallel Execution ER - 9614703
2223    ----------------------------------------------------------------------
2224    PROCEDURE process_act_budgets (
2225       x_return_status     OUT NOCOPY      VARCHAR2,
2226       x_msg_count         OUT NOCOPY      NUMBER,
2227       x_msg_data          OUT NOCOPY      VARCHAR2,
2228       p_act_budgets_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type,
2229       p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type,
2230       x_act_budget_id     OUT NOCOPY      NUMBER,
2231       x_utilized_amount   OUT NOCOPY      NUMBER
2232    ) IS
2233       lx_ozf_act_budgets_tbl    OZF_UTILITY_PVT.ozf_act_budgets_table;
2234       lx_ozf_funds_old_rectype OZF_UTILITY_PVT.ozf_funds_all_b_rectype;
2235       lx_ozf_funds_new_tbl OZF_UTILITY_PVT.ozf_funds_table;
2236       l_batch_type VARCHAR2(30);
2237    BEGIN
2238       process_act_budgets (
2239           x_return_status     => x_return_status,
2240           x_msg_count         => x_msg_count,
2241           x_msg_data          => x_msg_data,
2242           p_act_budgets_rec   => p_act_budgets_rec,
2243           p_act_util_rec      => p_act_util_rec,
2244           x_act_budget_id     => x_act_budget_id,
2245           x_utilized_amount   => x_utilized_amount,
2246           p_batch_type	     =>    l_batch_type,
2247           px_ozf_act_budgets_tbl => lx_ozf_act_budgets_tbl,
2248           px_ozf_funds_old_rectype      =>  lx_ozf_funds_old_rectype,
2249           px_ozf_funds_new_tbl      =>  lx_ozf_funds_new_tbl		-- For TPA Parallel Execution ER - 9614703
2250       );
2251    END process_act_budgets;
2252 
2253    --added by nirprasa for bug
2254    PROCEDURE process_act_budgets (
2255       x_return_status     OUT NOCOPY      VARCHAR2,
2256       x_msg_count         OUT NOCOPY      NUMBER,
2257       x_msg_data          OUT NOCOPY      VARCHAR2,
2258       p_act_budgets_rec   IN       ozf_actbudgets_pvt.act_budgets_rec_type,
2259       p_act_util_rec     IN       ozf_actbudgets_pvt.act_util_rec_type,
2260       x_act_budget_id     OUT NOCOPY      NUMBER,
2261       x_utilized_amount   OUT NOCOPY      NUMBER,
2262       x_utilization_id   OUT NOCOPY      NUMBER
2263    ) IS
2264       lx_ozf_act_budgets_tbl    OZF_UTILITY_PVT.ozf_act_budgets_table;
2265       lx_ozf_funds_old_rectype OZF_UTILITY_PVT.ozf_funds_all_b_rectype;
2266       lx_ozf_funds_new_tbl OZF_UTILITY_PVT.ozf_funds_table;
2267       l_batch_type VARCHAR2(30);
2268    BEGIN
2269       process_act_budgets (
2270           x_return_status     => x_return_status,
2271           x_msg_count         => x_msg_count,
2272           x_msg_data          => x_msg_data,
2273           p_act_budgets_rec   => p_act_budgets_rec,
2274           p_act_util_rec      => p_act_util_rec,
2275           x_act_budget_id     => x_act_budget_id,
2276           x_utilized_amount   => x_utilized_amount,
2277 	  p_batch_type	     =>    l_batch_type,
2278           px_ozf_act_budgets_tbl => lx_ozf_act_budgets_tbl,
2279           px_ozf_funds_old_rectype      =>  lx_ozf_funds_old_rectype,
2280           px_ozf_funds_new_tbl      =>  lx_ozf_funds_new_tbl,		-- For TPA Parallel Execution ER - 9614703
2281           x_utilization_id  => x_utilization_id
2282       );
2283    END process_act_budgets;
2284 
2285 ---------------------------------------------------------------------
2286 -- PROCEDURE
2287 --    post_scan_data_amount
2288 --
2289 -- PURPOSE
2290 -- This procedure is called by post_utilized_budget  when offer type is "SCAN_DATA' .
2291 -- It is used to create utilized records for scan data offer when offer start date reaches:
2292 
2293 -- PARAMETERS
2294 --       p_offer_id
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 --      ,x_msg_count       OUT      NUMBER
2299 --      ,x_msg_data        OUT      VARCHAR2
2300 --      ,x_return_status   OUT      VARCHAR2)
2301 
2302 -- NOTES
2303 -- HISTORY
2304 --    09/24/2002  feliu  Create.
2305 ----------------------------------------------------------------------
2306 
2307 PROCEDURE post_scan_data_amount (
2308       p_offer_id        IN       NUMBER
2309      ,p_api_version     IN       NUMBER
2310      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
2311      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
2312      ,p_check_date      IN       VARCHAR2 := fnd_api.g_true -- do date validation
2313      ,x_msg_count       OUT NOCOPY      NUMBER
2314      ,x_msg_data        OUT NOCOPY      VARCHAR2
2315      ,x_return_status   OUT NOCOPY      VARCHAR2
2316 ) IS
2317       l_api_version           NUMBER                                  := 1.0;
2318       l_return_status         VARCHAR2 (1)                            := fnd_api.g_ret_sts_success;
2319       l_msg_data               VARCHAR2 (2000);
2320       l_msg_count              NUMBER;
2321       l_api_name              VARCHAR2 (60)                           := 'post_scan_data_amount';
2322       l_full_name        CONSTANT VARCHAR2 (90)                           :=    g_pkg_name
2323                                                                              || '.'
2324                                                                              || l_api_name;
2325       l_product_id                NUMBER;
2326       l_offer_start_date          DATE;
2327       l_act_budget_id             NUMBER;
2328       l_act_budgets_rec           ozf_actbudgets_pvt.act_budgets_rec_type;
2329       l_act_util_rec              ozf_actbudgets_pvt.act_util_rec_type ;
2330       l_amount                    NUMBER                                  := 0;
2331       l_converted_amt             NUMBER;
2332       l_perform_util              VARCHAR2 (1);
2333       l_level_type_code           VARCHAR2 (30);
2334       l_scan_value                NUMBER;
2335       l_forecast_unit             NUMBER;
2336       l_quantity                  NUMBER;
2337       l_act_product_id            NUMBER;
2338       l_total_committed_amt       NUMBER;
2339       l_total_utilized_amt        NUMBER;
2340       l_currency_code             VARCHAR2(30);
2341       l_unit                      NUMBER;
2342       l_acct_closed_flag          VARCHAR2(1);
2343       l_cust_acct_id              NUMBER;
2344       l_cust_type                 VARCHAR2(30);
2345       l_offer_owner               NUMBER;
2346       l_org_id                    NUMBER;
2347       l_cust_setup_id             NUMBER;
2348       l_req_header_id             NUMBER;
2349 
2350      --get offer start data and currency.
2351       CURSOR c_offer_date IS
2352          SELECT qp.start_date_active, NVL(qp.currency_code, ofs.fund_request_curr_code) currency_code,
2353                 NVL(ofs.account_closed_flag,'N'),ofs.qualifier_id, ofs.qualifier_type,ofs.owner_id,ofs.custom_setup_id,
2354                 ofs.org_id
2355          FROM qp_list_headers_b qp,ozf_offers ofs
2356          WHERE qp.list_header_id = p_offer_id
2357          AND qp.list_header_id = ofs.qp_list_header_id;
2358 
2359       --get product information.
2360       CURSOR c_off_products (p_offer_id IN NUMBER) IS
2361          SELECT activity_product_id,DECODE (level_type_code, 'PRODUCT', inventory_item_id, category_id) product_id
2362                ,level_type_code,scan_value,scan_unit_forecast,quantity
2363          FROM ams_act_products
2364          WHERE act_product_used_by_id = p_offer_id
2365          AND arc_act_product_used_by = 'OFFR';
2366 
2367       --kdass 08-Jun-2005 Bug 4415878 SQL Repository Fix - changed the cursor query
2368       -- get committed budget information.
2369       CURSOR c_prod_budgets (p_offer_id IN NUMBER) IS
2370          SELECT NVL(plan_curr_committed_amt,0) approved_amount
2371                 ,fund_id
2372                 ,fund_currency currency_code
2373          FROM ozf_object_fund_summary
2374          WHERE object_id =p_offer_id
2375          AND object_type = 'OFFR';
2376 
2377 /*
2378          SELECT SUM (approved_amount) approved_amount, fund_id, currency_code
2379          FROM (
2380                SELECT NVL(plan_curr_amount,0) approved_amount, fund_id, currency_code
2381                FROM ozf_funds_utilized_all_b
2382                WHERE utilization_type = 'REQUEST'
2383                AND component_type = 'OFFR'
2384                AND component_id = p_offer_id
2385                UNION ALL
2386                SELECT NVL(-plan_curr_amount,0) approved_amount, fund_id, currency_code
2387                FROM ozf_funds_utilized_all_b
2388                WHERE utilization_type = 'TRANSFER'
2389                AND plan_type = 'OFFR'
2390                AND plan_id = p_offer_id
2391               ) GROUP BY fund_id, currency_code;
2392 
2393 
2394       CURSOR c_prod_budgets (p_offer_id IN NUMBER) IS
2395          SELECT SUM(NVL(DECODE(utilization_type, 'REQUEST',util.plan_curr_amount,-util.plan_curr_amount),0)) approved_amount,
2396             util.fund_id,util.currency_code
2397          FROM ozf_funds_utilized_all_b util
2398          WHERE util.utilization_type IN ('REQUEST','TRANSFER')
2399          AND DECODE(util.utilization_type,'REQUEST', util.component_type,util.plan_type) = 'OFFR'
2400          AND DECODE(util.utilization_type,'REQUEST', util.component_id,util.plan_id) = p_offer_id
2401          GROUP BY util.fund_id,util.currency_code;
2402       */
2403 
2404       --kdass 08-Jun-2005 Bug 4415878 SQL Repository Fix - changed the cursor query
2405       -- get total committed and utilized amount
2406       CURSOR c_committed_budgets(p_offer_id IN NUMBER) IS
2407         SELECT SUM(NVL(plan_curr_committed_amt,0))
2408         FROM ozf_object_fund_summary
2409         WHERE object_id =p_offer_id
2410         AND object_type = 'OFFR';
2411 /*
2412          SELECT SUM (approved_amount)
2413          FROM (SELECT NVL(plan_curr_amount,0) approved_amount
2414                FROM ozf_funds_utilized_all_b
2415                WHERE utilization_type = 'REQUEST'
2416                  AND component_type = 'OFFR'
2417                  AND component_id = p_offer_id
2418                UNION ALL
2419                SELECT NVL(-plan_curr_amount,0) approved_amount
2420                FROM ozf_funds_utilized_all_b
2421                WHERE utilization_type = 'TRANSFER'
2422                  AND plan_type = 'OFFR'
2423                  AND plan_id = p_offer_id);
2424 
2425       CURSOR c_committed_budgets(p_offer_id IN NUMBER) IS
2426         SELECT SUM(DECODE(utilization_type,'REQUEST',plan_curr_amount,'TRANSFER',-plan_curr_amount))
2427         FROM ozf_funds_utilized_all_b
2428         WHERE utilization_type IN ('REQUEST','TRANSFER')
2429         AND DECODE(utilization_type,'REQUEST', component_type,plan_type) = 'OFFR'
2430         AND DECODE(utilization_type,'REQUEST', component_id,plan_id) = p_offer_id;
2431       */
2432 
2433       CURSOR c_utilized_budgets(p_offer_id IN NUMBER) IS
2434         SELECT NVL(SUM(plan_curr_amount),0)
2435         FROM ozf_funds_utilized_all_b
2436         WHERE plan_id = p_offer_id
2437         AND  plan_type = 'OFFR'
2438         AND  utilization_type ='ACCRUAL';
2439 
2440       CURSOR c_req_date(p_offer_id IN NUMBER) IS
2441         SELECT request_header_id
2442         FROM ozf_request_headers_all_b
2443         WHERE offer_id =p_offer_id;
2444 
2445 /*
2446       CURSOR c_get_cust_account_id(p_party_id IN NUMBER) IS
2447         select max(cust_account_id) from hz_cust_accounts
2448         where party_id = p_party_id
2449         and status= 'A';
2450 */
2451 
2452       --Added for bug 7030415
2453       CURSOR c_get_conversion_type( p_org_id IN NUMBER) IS
2454         SELECT exchange_rate_type
2455         FROM   ozf_sys_parameters_all
2456         WHERE  org_id = p_org_id;
2457 
2458      l_exchange_rate_type VARCHAR2(30) := FND_API.G_MISS_CHAR;
2459      l_rate               NUMBER;
2460      l_offer_org_id       NUMBER;
2461 
2462    BEGIN
2463       SAVEPOINT post_scan_data_amount;
2464       IF G_DEBUG THEN
2465          ozf_utility_pvt.debug_message (   l_full_name || ': start');
2466       END IF;
2467       x_return_status            := fnd_api.g_ret_sts_success;
2468 
2469       IF fnd_api.to_boolean (p_init_msg_list) THEN
2470          fnd_msg_pub.initialize;
2471       END IF;
2472 
2473       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
2474          RAISE fnd_api.g_exc_unexpected_error;
2475       END IF;
2476 
2477       -- get total committed and utilized amount.
2478       OPEN c_committed_budgets(p_offer_id);
2479       FETCH c_committed_budgets INTO l_total_committed_amt;
2480       CLOSE c_committed_budgets;
2481 
2482       -- get total utilized and utilized amount.
2483       OPEN c_utilized_budgets(p_offer_id);
2484       FETCH c_utilized_budgets INTO l_total_utilized_amt;
2485       CLOSE c_utilized_budgets;
2486 
2487       -- check wether date validation is reqd
2488       OPEN c_offer_date;
2489       FETCH c_offer_date INTO l_offer_start_date,l_currency_code,
2490             l_acct_closed_flag,l_cust_acct_id,l_cust_type,l_offer_owner,l_cust_setup_id,l_offer_org_id;
2491       CLOSE c_offer_date;
2492       -- for special pricing, get request_header_id.
2493       IF l_cust_setup_id = 117 THEN
2494          OPEN c_req_date(p_offer_id);
2495          FETCH c_req_date INTO l_req_header_id;
2496          CLOSE c_req_date;
2497       END IF;
2498 
2499 
2500       -- check wether date validation is reqd
2501       IF p_check_date = fnd_api.g_true THEN
2502      -- if the offer start date is today or has passed then only adjust
2503          IF TRUNC(l_offer_start_date) <= TRUNC(SYSDATE) THEN
2504             l_perform_util             := 'T';
2505          ELSE
2506             l_perform_util             := 'F';
2507          END IF;
2508       ELSE
2509          -- donot check date
2510          l_perform_util             := 'T';
2511       END IF;
2512 
2513       --if system date reaches start_date and did not post before by checking utilized amount.
2514       IF l_perform_util = 'T' AND l_acct_closed_flag = 'N'  AND l_total_utilized_amt = 0 THEN
2515          OPEN c_off_products (p_offer_id);
2516 
2517          <<offer_prdt_loop>>
2518          LOOP
2519             FETCH c_off_products INTO l_act_product_id,l_product_id, l_level_type_code,l_scan_value,l_forecast_unit,l_quantity;
2520             EXIT WHEN c_off_products%NOTFOUND;
2521 
2522             FOR l_prod_budget_rec IN c_prod_budgets (p_offer_id)
2523             LOOP
2524                -- change later if a error has to be raised or not.
2525             /*   IF c_prod_budgets%NOTFOUND THEN
2526                   ozf_utility_pvt.error_message ('OZF_ACT_BUDG_UTIL_OVER');
2527                END IF;
2528              */
2529                EXIT WHEN c_prod_budgets%NOTFOUND;
2530                --get request amount proportionaly for total committed amount.
2531                l_unit := ozf_utility_pvt.currround(l_prod_budget_rec.approved_amount / l_total_committed_amt * l_forecast_unit
2532                                                    ,l_currency_code) ;
2533 
2534                -- 08/13/2004 kdass fix for 11.5.9 bug 3830164, divided the amount by the quantity
2535                --l_amount := l_unit * l_scan_value; -- in object currency.
2536                l_amount := l_unit * l_scan_value / l_quantity; -- in object currency.
2537 
2538                IF G_DEBUG THEN
2539                   ozf_utility_pvt.debug_message ( 'scan unit: ' ||  l_unit);
2540 
2541                   ozf_utility_pvt.debug_message ( 'scan amount : ' ||  l_amount);
2542                END IF;
2543 
2544                IF l_amount <> 0 THEN
2545                -- convert the object currency amount into fund currency
2546                    IF l_prod_budget_rec.currency_code = l_currency_code THEN
2547                       l_converted_amt            := l_amount;
2548                    ELSE
2549                   -- call the currency conversion wrapper
2550                   --Added for bug 7030415
2551 
2552                   OPEN c_get_conversion_type(l_offer_org_id);
2553                   FETCH c_get_conversion_type INTO l_exchange_rate_type;
2554                   CLOSE c_get_conversion_type;
2555 
2556                       ozf_utility_pvt.convert_currency (
2557                            x_return_status=> x_return_status
2558                            ,p_from_currency=> l_currency_code
2559                            ,p_conv_type=> l_exchange_rate_type
2560                            ,p_to_currency=> l_prod_budget_rec.currency_code
2561                            ,p_from_amount=> l_amount
2562                            ,x_to_amount=> l_converted_amt
2563                            ,x_rate=> l_rate
2564                           );
2565 
2566                       IF x_return_status <> fnd_api.g_ret_sts_success THEN
2567                           x_return_status            := fnd_api.g_ret_sts_error;
2568                           RAISE fnd_api.g_exc_error;
2569                       END IF;
2570                    END IF;
2571 
2572                   l_act_budgets_rec.request_amount := l_amount; -- in object currency.
2573                   l_act_budgets_rec.act_budget_used_by_id := p_offer_id;
2574                   l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
2575                   l_act_budgets_rec.budget_source_type := 'OFFR';
2576                   l_act_budgets_rec.budget_source_id := p_offer_id;
2577                   l_act_budgets_rec.request_currency := l_currency_code;
2578                   l_act_budgets_rec.request_date := SYSDATE;
2579                   l_act_budgets_rec.status_code := 'APPROVED';
2580                   l_act_budgets_rec.user_status_id := ozf_utility_pvt.get_default_user_status (
2581                                              'OZF_BUDGETSOURCE_STATUS'
2582                                              ,l_act_budgets_rec.status_code
2583                                             );
2584                   l_act_budgets_rec.transfer_type := 'UTILIZED';
2585                   l_act_budgets_rec.approval_date := SYSDATE;
2586                   l_act_budgets_rec.requester_id := l_offer_owner;
2587 
2588                   l_act_budgets_rec.approver_id :=
2589                                                ozf_utility_pvt.get_resource_id (fnd_global.user_id);
2590                   -- when workflow goes through without approval, fnd_global.user_id is not passed.
2591                   IF l_act_budgets_rec.approver_id = -1 THEN
2592                      l_act_budgets_rec.approver_id := l_offer_owner;
2593                   END IF;
2594 
2595                   l_act_budgets_rec.justification :=
2596                                              fnd_message.get_string ('OZF', 'OZF_ACT_BUDGET_SCANDATA_UTIL');
2597                   l_act_budgets_rec.parent_source_id := l_prod_budget_rec.fund_id;
2598                   l_act_budgets_rec.parent_src_curr := l_prod_budget_rec.currency_code;
2599                   l_act_budgets_rec.parent_src_apprvd_amt := l_converted_amt; -- in budget currency.
2600                   l_act_util_rec.product_id := l_product_id ;
2601                   l_act_util_rec.product_level_type := l_level_type_code;
2602                   l_act_util_rec.gl_date := sysdate;
2603                   l_act_util_rec.scan_unit := l_unit ;
2604                   l_act_util_rec.scan_unit_remaining := l_unit;
2605                   l_act_util_rec.activity_product_id := l_act_product_id;
2606                   l_act_util_rec.utilization_type :='UTILIZED'; --will changed to 'ACCRUAL' in create_fund_utilization.
2607 /*
2608                   --kdass 23-FEB-2004 fix for bug 3426061
2609                   -- If the Qualifier is a Buying group, then store Customer Account ID instead of Party ID
2610                   IF l_cust_type = 'BUYER' THEN
2611                      OPEN c_get_cust_account_id(l_cust_acct_id);
2612                      FETCH c_get_cust_account_id INTO l_cust_acct_id;
2613                      CLOSE c_get_cust_account_id;
2614                   END IF;
2615 
2616                   l_act_util_rec.cust_account_id := l_cust_acct_id;
2617 */
2618                   --nirprasa,12.1.1
2619                   l_act_util_rec.plan_currency_code := l_currency_code;
2620                   l_act_util_rec.fund_request_currency_code := l_currency_code;
2621                   --nirprasa,12.1.1
2622                   l_org_id := find_org_id (l_act_budgets_rec.parent_source_id);
2623                   -- set org_context since workflow mailer does not set the context
2624                   set_org_ctx (l_org_id);
2625                   -- for special pricing, add reference type and id.
2626                   IF l_cust_setup_id = 117 THEN
2627                      l_act_util_rec.reference_id := l_req_header_id;
2628                      l_act_util_rec.reference_type := 'SPECIAL_PRICE';
2629                   END IF;
2630 
2631                   process_act_budgets (x_return_status  => l_return_status,
2632                                        x_msg_count => x_msg_count,
2633                                        x_msg_data   => x_msg_data,
2634                                        p_act_budgets_rec => l_act_budgets_rec,
2635                                        p_act_util_rec   =>l_act_util_rec,
2636                                        x_act_budget_id  => l_act_budget_id
2637                                        ) ;
2638 
2639                   IF l_return_status = fnd_api.g_ret_sts_error THEN
2640                      RAISE fnd_api.g_exc_error;
2641                   ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
2642                      RAISE fnd_api.g_exc_unexpected_error;
2643                   END IF;
2644                END IF; -- for  amount
2645 
2646                IF G_DEBUG THEN
2647                   ozf_utility_pvt.debug_message (   l_full_name
2648                                               || ': end create act budgets  ');
2649                END IF;
2650                l_act_budgets_rec          := NULL;
2651                l_act_util_rec             := NULL;
2652             END LOOP;
2653 
2654          END LOOP offer_prdt_loop;
2655 
2656          CLOSE c_off_products;
2657       END IF;
2658 
2659 
2660       IF      fnd_api.to_boolean (p_commit)
2661           AND l_return_status = fnd_api.g_ret_sts_success THEN
2662          COMMIT;
2663       END IF;
2664 
2665 
2666       fnd_msg_pub.count_and_get (
2667          p_encoded=> fnd_api.g_false
2668         ,p_count=> x_msg_count
2669         ,p_data=> x_msg_data
2670       );
2671       IF G_DEBUG THEN
2672          ozf_utility_pvt.debug_message (   l_full_name || ': end');
2673       END IF;
2674 
2675    EXCEPTION
2676       WHEN fnd_api.g_exc_error THEN
2677          ROLLBACK TO post_scan_data_amount;
2678          x_return_status            := fnd_api.g_ret_sts_error;
2679          fnd_msg_pub.count_and_get (
2680             p_count=> x_msg_count
2681            ,p_data=> x_msg_data
2682            ,p_encoded=> fnd_api.g_false
2683          );
2684       WHEN fnd_api.g_exc_unexpected_error THEN
2685          ROLLBACK TO post_scan_data_amount;
2686          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2687          fnd_msg_pub.count_and_get (
2688             p_count=> x_msg_count
2689            ,p_data=> x_msg_data
2690            ,p_encoded=> fnd_api.g_false
2691          );
2692       WHEN OTHERS THEN
2693          ROLLBACK TO post_scan_data_amount;
2694          x_return_status            := fnd_api.g_ret_sts_unexp_error;
2695 
2696          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2697             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
2698          END IF;
2699 
2700          fnd_msg_pub.count_and_get (
2701             p_count=> x_msg_count
2702            ,p_data=> x_msg_data
2703            ,p_encoded=> fnd_api.g_false
2704          );
2705      END Post_scan_data_amount;
2706 
2707 
2708 ---------------------------------------------------------------------
2709 -- PROCEDURE
2710 --    post_lumpsum_amount
2711 --
2712 -- PURPOSE
2713 -- This procedure is called by post_utilized_budget  when offer type is "LUMPSUM' .
2714 -- It is used to create utilized records for lumpsum offer when offer start date reaches:
2715 
2716 -- PARAMETERS
2717 --       p_offer_id
2718 --      ,p_api_version     IN       NUMBER
2719 --      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
2720 --      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
2721 --      ,x_msg_count       OUT      NUMBER
2722 --      ,x_msg_data        OUT      VARCHAR2
2723 --      ,x_return_status   OUT      VARCHAR2)
2724 
2725 -- NOTES
2726 -- HISTORY
2727 --    09/24/2002  feliu  Create.
2728 --    10/07/2005  feliu  rewrite to fix issue for bug 4628081
2729 ----------------------------------------------------------------------
2730 
2731    PROCEDURE post_lumpsum_amount (
2732       p_offer_id        IN       NUMBER
2733      ,p_api_version     IN       NUMBER
2734      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
2735      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
2736      ,p_check_date      IN       VARCHAR2 := fnd_api.g_true -- do date validation
2737      ,x_msg_count       OUT NOCOPY      NUMBER
2738      ,x_msg_data        OUT NOCOPY      VARCHAR2
2739      ,x_return_status   OUT NOCOPY      VARCHAR2
2740    ) IS
2741       l_return_status             VARCHAR2 (10)                           := fnd_api.g_ret_sts_success;
2742       l_api_name         CONSTANT VARCHAR2 (30)                           := 'Posting_lumpsum_amount';
2743       l_api_version      CONSTANT NUMBER                                  := 1.0;
2744       l_full_name        CONSTANT VARCHAR2 (90)                           :=    g_pkg_name
2745                                                                              || '.'
2746                                                                              || l_api_name;
2747       l_product_id                NUMBER;
2748       l_fund_id                   NUMBER;
2749       l_offer_start_date          DATE;
2750       l_offer_end_date            DATE;
2751       l_act_budget_id             NUMBER;
2752       l_act_budgets_rec           ozf_actbudgets_pvt.act_budgets_rec_type;
2753       l_act_util_rec              ozf_actbudgets_pvt.act_util_rec_type ;
2754       l_amount                    NUMBER                                  := 0;
2755       l_converted_amt             NUMBER;
2756       l_perform_util              VARCHAR2 (1);
2757       l_offer_total_amount        NUMBER;
2758       l_offer_distribution_type   VARCHAR2 (30);
2759       l_total_qty                 NUMBER;
2760       l_level_type_code         VARCHAR2 (30);
2761       l_currency_code             VARCHAR2 (30);
2762       l_total_committed_amt       NUMBER;
2763       l_total_utilized_amt        NUMBER;
2764       l_fund_utilized_amt         NUMBER;
2765       l_utilized_amt              NUMBER;
2766       l_custom_setup_id           NUMBER;
2767       l_acct_closed_flag       VARCHAR2 (1);
2768       l_spread_flag       VARCHAR2 (1);
2769       l_cust_type         VARCHAR2(30);
2770       l_cust_acct_id     NUMBER;
2771       l_offer_owner     NUMBER;
2772       l_org_id             NUMBER;
2773       l_offer_org_id     NUMBER;
2774       l_date                DATE;
2775 
2776       --get offer date and currency.
2777       CURSOR c_offer_date IS
2778          SELECT qp.start_date_active,qp.end_date_active, NVL(qp.currency_code, ofs.fund_request_curr_code) currency_code,
2779                 ofs.custom_setup_id,NVL(ofs.account_closed_flag,'N'),ofs.qualifier_id, ofs.qualifier_type,
2780                 ofs.org_id
2781          FROM qp_list_headers_b qp,ozf_offers ofs
2782          WHERE qp.list_header_id = p_offer_id
2783          AND qp.list_header_id = ofs.qp_list_header_id;
2784 
2785       ---get distribution
2786       CURSOR c_offer_distribution IS
2787          SELECT offer_amount
2788                ,distribution_type,owner_id
2789          FROM ozf_offers
2790          WHERE qp_list_header_id = p_offer_id;
2791 
2792       --get product information.
2793       CURSOR c_off_products (p_offer_id IN NUMBER) IS
2794          SELECT DECODE (level_type_code, 'PRODUCT', inventory_item_id, category_id) product_id
2795                ,SUM(line_lumpsum_qty) amount, level_type_code
2796          FROM ams_act_products
2797          WHERE act_product_used_by_id = p_offer_id
2798          AND arc_act_product_used_by = 'OFFR'
2799          GROUP BY inventory_item_id,level_type_code,category_id; -- added by feliu to fix bug 4861647
2800 
2801       --get sum of lumpsum line amount.
2802       CURSOR c_off_pdts_total_qty (p_offer_id IN NUMBER) IS
2803          SELECT SUM (line_lumpsum_qty) total_quantity
2804          FROM ams_act_products
2805          WHERE act_product_used_by_id = p_offer_id
2806          AND arc_act_product_used_by = 'OFFR';
2807 
2808       --kdass 08-Jun-2005 Bug 4415878 SQL Repository Fix - changed the cursor query
2809       -- get committed budget information.
2810       CURSOR c_prod_budgets (p_offer_id IN NUMBER) IS
2811          SELECT NVL(plan_curr_committed_amt,0) approved_amount
2812                 ,fund_id
2813                 ,fund_currency currency_code
2814          FROM ozf_object_fund_summary
2815          WHERE object_id =p_offer_id
2816          AND object_type = 'OFFR';
2817 
2818          /*
2819 
2820          SELECT SUM (approved_amount) approved_amount, fund_id, currency_code
2821          FROM (
2822                SELECT NVL(plan_curr_amount,0) approved_amount, fund_id, currency_code
2823                FROM ozf_funds_utilized_all_b
2824                WHERE utilization_type = 'REQUEST'
2825                AND component_type = 'OFFR'
2826                AND component_id = p_offer_id
2827                UNION ALL
2828                SELECT NVL(-plan_curr_amount,0) approved_amount, fund_id, currency_code
2829                FROM ozf_funds_utilized_all_b
2830                WHERE utilization_type = 'TRANSFER'
2831                AND plan_type = 'OFFR'
2832                AND plan_id = p_offer_id
2833               ) GROUP BY fund_id, currency_code;
2834 
2835 
2836       CURSOR c_prod_budgets (p_offer_id IN NUMBER) IS
2837          SELECT SUM(NVL(DECODE(utilization_type, 'REQUEST',util.plan_curr_amount,-util.plan_curr_amount),0)) approved_amount,
2838             util.fund_id,util.currency_code
2839          FROM ozf_funds_utilized_all_b util
2840          WHERE util.utilization_type IN ('REQUEST','TRANSFER')
2841          AND DECODE(util.utilization_type,'REQUEST', util.component_type,util.plan_type) = 'OFFR'
2842          AND DECODE(util.utilization_type,'REQUEST', util.component_id,util.plan_id) = p_offer_id
2843          GROUP BY util.fund_id,util.currency_code;
2844       */
2845 
2846       --kdass 08-Jun-2005 Bug 4415878 SQL Repository Fix - changed the cursor query
2847       -- get total committed and utilized amount
2848       CURSOR c_committed_budgets(p_offer_id IN NUMBER) IS
2849         SELECT SUM(NVL(plan_curr_committed_amt,0))
2850         FROM ozf_object_fund_summary
2851         WHERE object_id =p_offer_id
2852         AND object_type = 'OFFR';
2853          /*
2854          SELECT SUM (approved_amount)
2855          FROM (SELECT NVL(plan_curr_amount,0) approved_amount
2856                FROM ozf_funds_utilized_all_b
2857                WHERE utilization_type = 'REQUEST'
2858                  AND component_type = 'OFFR'
2859                  AND component_id = p_offer_id
2860                UNION ALL
2861                SELECT NVL(-plan_curr_amount,0) approved_amount
2862                FROM ozf_funds_utilized_all_b
2863                WHERE utilization_type = 'TRANSFER'
2864                  AND plan_type = 'OFFR'
2865                  AND plan_id = p_offer_id);
2866 
2867       CURSOR c_committed_budgets(p_offer_id IN NUMBER) IS
2868         SELECT SUM(DECODE(utilization_type,'REQUEST',plan_curr_amount,'TRANSFER',-plan_curr_amount))
2869         FROM ozf_funds_utilized_all_b
2870         WHERE utilization_type IN ('REQUEST','TRANSFER')
2871         AND DECODE(utilization_type,'REQUEST', component_type,plan_type) = 'OFFR'
2872         AND DECODE(utilization_type,'REQUEST', component_id,plan_id) = p_offer_id;
2873       */
2874 
2875       CURSOR c_utilization_budgets(p_offer_id IN NUMBER) IS
2876         SELECT NVL(SUM(plan_curr_amount),0), MAX(creation_date)
2877         FROM ozf_funds_utilized_all_b
2878         WHERE plan_id = p_offer_id
2879         AND  plan_type = 'OFFR'
2880         AND  utilization_type ='ACCRUAL';
2881 
2882        -- get total utilized amount for this product and this budget.
2883      CURSOR c_utilized_budgets(p_offer_id IN NUMBER,p_fund_id IN NUMBER) IS
2884         SELECT SUM(util.plan_curr_amount)
2885         FROM ozf_funds_utilized_all_b util
2886         WHERE util.component_id = p_offer_id
2887         AND util.component_type = 'OFFR'
2888         AND util.utilization_type ='ACCRUAL'
2889         --AND product_id =p_product_id
2890         AND fund_id = p_fund_id;
2891 
2892     CURSOR l_scatter_posting (p_custom_setup_id IN NUMBER) IS
2893         SELECT attr_available_flag
2894         FROM   ams_custom_setup_attr
2895         WHERE  custom_setup_id = p_custom_setup_id
2896         AND    object_attribute = 'SCPO';
2897 
2898    --Added for bug 7030415
2899    CURSOR c_get_conversion_type( p_org_id IN NUMBER) IS
2900         SELECT exchange_rate_type
2901         FROM   ozf_sys_parameters_all
2902         WHERE  org_id = p_org_id;
2903 
2904    l_exchange_rate_type VARCHAR2(30) := FND_API.G_MISS_CHAR;
2905    l_rate               NUMBER;
2906 
2907     l_count NUMBER;
2908     l_limit_row NUMBER := 100;
2909     l_amount_remaining NUMBER;
2910 
2911    TYPE itemIdTbl       IS TABLE OF ams_act_products.inventory_item_id%TYPE;
2912    TYPE lumsumAmtTbl       IS TABLE OF ams_act_products.line_lumpsum_qty%TYPE;
2913    TYPE levelTypeTbl       IS TABLE OF ams_act_products.level_type_code%TYPE;
2914 
2915    l_itemId_tbl    itemIdTbl;
2916    l_lumsumAmt_tbl  lumsumAmtTbl;
2917    l_levelType_tbl  levelTypeTbl;
2918 
2919    l_spread_amount_remaining NUMBER;
2920    l_last_offer_accrual_date DATE;
2921    l_last_prod_accrual_date DATE;
2922 
2923    l_offer_data        CLOB;
2924    l_item_key          VARCHAR2(50);
2925    l_event_name        VARCHAR2(80);
2926    l_parameter_list    wf_parameter_list_t;
2927 
2928    BEGIN
2929       SAVEPOINT Posting_lumpsum_amount;
2930 
2931       IF G_DEBUG THEN
2932          ozf_utility_pvt.debug_message (   l_full_name || ': start');
2933       END IF;
2934       x_return_status            := fnd_api.g_ret_sts_success;
2935 
2936       IF fnd_api.to_boolean (p_init_msg_list) THEN
2937          fnd_msg_pub.initialize;
2938       END IF;
2939 
2940       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
2941          RAISE fnd_api.g_exc_unexpected_error;
2942       END IF;
2943 
2944       -- get total committed amount.
2945       OPEN c_committed_budgets(p_offer_id);
2946       FETCH c_committed_budgets INTO l_total_committed_amt;
2947       CLOSE c_committed_budgets;
2948 
2949       -- get total utilized amount.
2950       OPEN c_utilization_budgets(p_offer_id);
2951       FETCH c_utilization_budgets INTO l_total_utilized_amt,l_last_offer_accrual_date;
2952       CLOSE c_utilization_budgets;
2953 
2954       OPEN c_offer_date;
2955       FETCH c_offer_date INTO l_offer_start_date,l_offer_end_date,l_currency_code,
2956             l_custom_setup_id,l_acct_closed_flag,l_cust_acct_id,l_cust_type,l_offer_org_id;
2957       CLOSE c_offer_date;
2958 
2959       -- get spread posting information.
2960       OPEN l_scatter_posting(l_custom_setup_id);
2961       FETCH l_scatter_posting INTO l_spread_flag;
2962       CLOSE l_scatter_posting;
2963 
2964       -- check wether date validation is reqd
2965       IF p_check_date = fnd_api.g_true THEN
2966      -- if the offer start date is today or has passed then only adjust
2967          IF TRUNC(l_offer_start_date) <= TRUNC(SYSDATE) THEN
2968             l_perform_util             := 'T';
2969          ELSE
2970             l_perform_util             := 'F';
2971          END IF;
2972       ELSE
2973          -- donot check date
2974          l_perform_util             := 'T';
2975       END IF;
2976 
2977       OPEN c_offer_distribution;
2978       FETCH c_offer_distribution INTO l_offer_total_amount, l_offer_distribution_type,l_offer_owner;
2979       CLOSE c_offer_distribution;
2980 
2981       --IF l_spread_flag = 'N' THEN 08/11/03 commented by feliu to fix bug 3091395
2982          validate_lumpsum_offer (p_qp_list_header_id => p_offer_id, x_return_status => x_return_status);
2983       --END IF;
2984 
2985       IF x_return_status <> fnd_api.g_ret_sts_success THEN
2986          x_return_status            := fnd_api.g_ret_sts_error;
2987          RAISE fnd_api.g_exc_error;
2988       END IF;
2989 
2990       IF G_DEBUG THEN
2991       ozf_utility_pvt.debug_message (  'l_perform_util ' || l_perform_util);
2992       ozf_utility_pvt.debug_message (  'l_acct_closed_flag ' || l_acct_closed_flag);
2993       ozf_utility_pvt.debug_message (  'l_total_utilized_amt ' || l_total_utilized_amt);
2994       ozf_utility_pvt.debug_message (  'l_offer_total_amount ' || l_offer_total_amount);
2995       ozf_utility_pvt.debug_message (  'p_offer_id ' || p_offer_id);
2996       ozf_utility_pvt.write_conc_log (  'l_total_committed_amt ' || l_total_committed_amt);
2997       END IF;
2998 
2999       --check if start date reaches, if account closed, and if already posted.
3000       --nirprasa,12.1.1 replace ROUND() by ozf_utility_pvt.currround() to use the currency precision instead
3001       --of hardcoded value.
3002       --nirprasa, start fix for bug 8625525
3003 
3004       IF l_perform_util = 'T' AND l_acct_closed_flag = 'N' AND  l_total_utilized_amt < l_total_committed_amt THEN
3005 
3006          OPEN c_off_products (p_offer_id);
3007 	 LOOP   -- AMITAMKU Fix for Bug 14180155 , Added loop so that the number of rows can be greater than or less than the l_limit_row value
3008 
3009          FETCH c_off_products BULK COLLECT INTO l_itemId_tbl,l_lumsumAmt_tbl,l_levelType_tbl LIMIT l_limit_row;
3010 
3011          FOR l_prod_budget_rec IN c_prod_budgets (p_offer_id) LOOP
3012 
3013             EXIT WHEN c_prod_budgets%NOTFOUND;
3014             l_amount_remaining := l_prod_budget_rec.approved_amount;
3015             l_offer_total_amount := l_total_committed_amt - NVL(l_total_utilized_amt,0);
3016             l_count := 0;
3017 
3018             --nirprasa, bug 8460909
3019             IF l_spread_flag = 'Y' THEN
3020                 IF TRUNC(sysdate) > TRUNC(l_offer_end_date) THEN
3021                    l_date := TRUNC(l_offer_end_date);
3022                 ELSE
3023                    l_date := TRUNC(sysdate);
3024                 END IF;
3025 
3026                 IF G_DEBUG THEN
3027                    ozf_utility_pvt.write_conc_log (  'l_date ' || l_date);
3028                    ozf_utility_pvt.write_conc_log (  'l_last_offer_accrual_date ' || l_last_offer_accrual_date);
3029                    ozf_utility_pvt.write_conc_log (  'l_total_committed_amt ' || l_total_committed_amt);
3030                    ozf_utility_pvt.write_conc_log (  'l_amount_remaining ' || l_amount_remaining);
3031                    ozf_utility_pvt.write_conc_log (  'l_total_utilized_amt ' || l_total_utilized_amt);
3032                 END IF;
3033 
3034                 IF l_last_offer_accrual_date IS NULL THEN
3035                    l_spread_amount_remaining := ozf_utility_pvt.currround(l_offer_total_amount * (l_date - TRUNC(l_offer_start_date) + 1) /(TRUNC(l_offer_end_date) - TRUNC(l_offer_start_date) + 1),l_prod_budget_rec.currency_code);
3036                 ELSE
3037                    l_spread_amount_remaining := ozf_utility_pvt.currround(l_offer_total_amount * (l_date - TRUNC(l_last_offer_accrual_date) ) /(TRUNC(l_offer_end_date) - TRUNC(l_last_offer_accrual_date)),l_prod_budget_rec.currency_code);
3038                 END IF;
3039                 l_spread_amount_remaining := ozf_utility_pvt.currround((l_prod_budget_rec.approved_amount / l_total_committed_amt) * l_spread_amount_remaining,l_prod_budget_rec.currency_code);
3040             END IF;
3041 
3042             FOR i IN NVL(l_itemId_tbl.FIRST, 1) .. NVL(l_itemId_tbl.LAST, 0) LOOP
3043                l_count := l_count + 1;
3044 
3045                IF G_DEBUG THEN
3046                   ozf_utility_pvt.write_conc_log (  '*****************l_count ' || l_count||'*****************');
3047                   ozf_utility_pvt.write_conc_log (  'l_amount ' || l_amount);
3048                   ozf_utility_pvt.write_conc_log (  'l_spread_flag ' || l_spread_flag);
3049                   ozf_utility_pvt.write_conc_log (  'l_spread_amount_remaining ' || l_spread_amount_remaining);
3050                END IF;
3051 
3052                IF l_offer_distribution_type = '%' THEN
3053                   l_amount   := ozf_utility_pvt.currround(l_offer_total_amount * l_lumsumAmt_tbl(i) / 100,l_currency_code);
3054                ELSIF l_offer_distribution_type = 'QTY' THEN
3055                  OPEN c_off_pdts_total_qty (p_offer_id);
3056                  FETCH c_off_pdts_total_qty INTO l_total_qty;
3057                  CLOSE c_off_pdts_total_qty;
3058                  --14-OCT-2008 bug 7382309 - changed from 100 to offer committed amountl_total_committed_amt
3059                  --l_amount  := ROUND(l_lumsumAmt_tblozf_utility_pvt.currround(i) * 100 / l_total_qty,2);
3060                  l_amount  := ozf_utility_pvt.currround(l_lumsumAmt_tbl(i) * l_offer_total_amount / l_total_qty,l_currency_code);
3061                ELSIF l_offer_distribution_type = 'AMT' THEN
3062                   OPEN c_off_pdts_total_qty (p_offer_id);
3063                   FETCH c_off_pdts_total_qty INTO l_total_qty;
3064                   CLOSE c_off_pdts_total_qty;
3065                   IF G_DEBUG THEN
3066                      ozf_utility_pvt.write_conc_log (  'l_lumsumAmt_tbl(i) ' || l_lumsumAmt_tbl(i));
3067                      ozf_utility_pvt.write_conc_log (  'l_offer_total_amount ' || l_offer_total_amount);
3068                      ozf_utility_pvt.write_conc_log (  'l_total_qty ' || l_total_qty);
3069                   END IF;
3070                   l_amount := ozf_utility_pvt.currround(l_lumsumAmt_tbl(i) * l_offer_total_amount / l_total_qty,l_currency_code) ;
3071                END IF;
3072 
3073 
3074 
3075                IF l_spread_flag = 'Y' THEN
3076                   --posted amount for this product since start date.
3077                   -- add if condition to fix bug 3407559. only have partial amount if sysdate is less than offer end date.
3078                   --7721879 Fix
3079                   IF  TRUNC(SYSDATE) < TRUNC(l_offer_end_date) THEN
3080                     l_last_prod_accrual_date := TRUNC(l_offer_end_date);
3081                   END IF;
3082 
3083                   IF TRUNC(sysdate) < TRUNC(l_offer_end_date) THEN
3084                      IF G_DEBUG THEN
3085                         ozf_utility_pvt.write_conc_log (  'l_offer_start_date ' || l_offer_start_date);
3086                         ozf_utility_pvt.write_conc_log (  'l_offer_end_date ' || l_offer_end_date);
3087                         ozf_utility_pvt.write_conc_log (  'l_last_offer_accrual_date ' || l_last_offer_accrual_date);
3088                         ozf_utility_pvt.write_conc_log (  'l_amount ' || l_amount);
3089                      END IF;
3090                      IF l_last_offer_accrual_date IS NULL THEN
3091                         l_amount := ozf_utility_pvt.currround(l_amount * (TRUNC(sysdate) - TRUNC(l_offer_start_date) + 1)/(TRUNC(l_offer_end_date) - TRUNC(l_offer_start_date) + 1),l_currency_code);
3092                      ELSE
3093                         l_amount := ozf_utility_pvt.currround(l_amount * (TRUNC(sysdate) - TRUNC(l_last_offer_accrual_date))/(TRUNC(l_offer_end_date) - TRUNC(l_last_offer_accrual_date)),l_currency_code);
3094                      END IF;
3095                   END IF;
3096                END IF;
3097 
3098               IF G_DEBUG THEN
3099                   ozf_utility_pvt.write_conc_log (  'posting amount ' || l_amount || '  for product: ' || l_itemId_tbl(i));
3100                   ozf_utility_pvt.write_conc_log (  'l_spread_amount_remaining ' || l_spread_amount_remaining);
3101                   ozf_utility_pvt.write_conc_log (  'l_prod_budget_rec.approved_amount  ' || l_prod_budget_rec.approved_amount );
3102                   ozf_utility_pvt.write_conc_log (  'l_total_committed_amt  ' || l_total_committed_amt );
3103                END IF;
3104 
3105                IF l_spread_flag = 'Y' THEN
3106                   l_utilized_amt := ozf_utility_pvt.currround((l_prod_budget_rec.approved_amount / l_total_committed_amt) * l_amount,l_prod_budget_rec.currency_code);
3107                ELSE
3108                   l_utilized_amt := ozf_utility_pvt.currround((l_prod_budget_rec.approved_amount / l_total_committed_amt) * l_amount,l_prod_budget_rec.currency_code);
3109                END IF;
3110 
3111                --nirprasa, end fix for bug 8625525
3112 
3113                IF G_DEBUG THEN
3114                 ozf_utility_pvt.write_conc_log (  ' l_utilized_amt ' || l_utilized_amt);
3115                 ozf_utility_pvt.write_conc_log (  ' l_count ' || l_count);
3116                 ozf_utility_pvt.write_conc_log (  ' l_itemId_tbl.COUNT ' || l_itemId_tbl.COUNT);
3117                END IF;
3118 
3119                IF l_count = l_itemId_tbl.COUNT THEN
3120                -- use remaining amount if it is last record to solve the issue for rounding.
3121                   IF l_spread_flag <> 'Y' THEN
3122                      l_utilized_amt := l_amount_remaining;
3123                   ELSE
3124                      IF G_DEBUG THEN
3125                      ozf_utility_pvt.debug_message (  ' l_spread_amount_remaining ' || l_spread_amount_remaining);
3126                      END IF;
3127 
3128                      l_utilized_amt := l_spread_amount_remaining;
3129 
3130                      END IF;
3131                   END IF;
3132 
3133                IF G_DEBUG THEN
3134                   ozf_utility_pvt.debug_message (  ' l_spread_amount_remaining1 ' || l_spread_amount_remaining);
3135                   ozf_utility_pvt.debug_message (  ' l_amount_remaining1 ' || l_amount_remaining);
3136                   ozf_utility_pvt.debug_message (  ' l_utilized_amt1 ' || l_utilized_amt);
3137                END IF;
3138 
3139                --7721879
3140                l_amount_remaining := l_amount_remaining - l_utilized_amt;
3141                l_spread_amount_remaining := l_spread_amount_remaining - l_utilized_amt;
3142 
3143                IF G_DEBUG THEN
3144                ozf_utility_pvt.debug_message (  ' l_spread_amount_remaining2 ' || l_spread_amount_remaining);
3145                ozf_utility_pvt.debug_message (  ' l_amount_remaining2 ' || l_amount_remaining);
3146                ozf_utility_pvt.debug_message (  ' l_utilized_amt2 ' || l_utilized_amt);
3147                END IF;
3148 
3149                IF G_DEBUG THEN
3150                  ozf_utility_pvt.debug_message (  ': lumpsum posting amount ' || l_utilized_amt);
3151                END IF;
3152 
3153                -- convert the object currency amount in to fund currency
3154                IF l_prod_budget_rec.currency_code = l_currency_code THEN
3155                   l_converted_amt            := l_utilized_amt;
3156                ELSE
3157                   --Added for bug 7030415
3158 
3159                   OPEN c_get_conversion_type(l_offer_org_id);
3160                   FETCH c_get_conversion_type INTO l_exchange_rate_type;
3161                   CLOSE c_get_conversion_type;
3162                   -- call the currency conversion wrapper
3163                   ozf_utility_pvt.convert_currency (
3164                      x_return_status=> x_return_status
3165                     ,p_from_currency=> l_currency_code
3166                     ,p_to_currency=> l_prod_budget_rec.currency_code
3167                     ,p_conv_type=> l_exchange_rate_type
3168                     ,p_from_amount=> l_utilized_amt
3169                     ,x_to_amount=> l_converted_amt
3170                     ,x_rate=> l_rate
3171                   );
3172 
3173                   IF x_return_status <> fnd_api.g_ret_sts_success THEN
3174                      x_return_status            := fnd_api.g_ret_sts_error;
3175                      RAISE fnd_api.g_exc_error;
3176                   END IF;
3177                END IF;
3178 
3179                IF G_DEBUG THEN
3180                ozf_utility_pvt.debug_message (  'LS CP l_converted_amt ' || l_converted_amt);
3181                END IF;
3182 
3183                IF l_converted_amt <> 0 THEN
3184                   l_act_budgets_rec.request_amount := l_utilized_amt; --in object currency.
3185                   l_act_budgets_rec.act_budget_used_by_id := p_offer_id;
3186                   l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3187                   l_act_budgets_rec.budget_source_type := 'OFFR';
3188                   l_act_budgets_rec.budget_source_id := p_offer_id;
3189                   l_act_budgets_rec.request_currency := l_currency_code;
3190                   l_act_budgets_rec.request_date := SYSDATE;
3191                   l_act_budgets_rec.status_code := 'APPROVED';
3192                   l_act_budgets_rec.user_status_id := ozf_utility_pvt.get_default_user_status (
3193                                                               'OZF_BUDGETSOURCE_STATUS'
3194                                                               ,l_act_budgets_rec.status_code
3195                                                               );
3196                   l_act_budgets_rec.transfer_type := 'UTILIZED';
3197                   l_act_budgets_rec.approval_date := SYSDATE;
3198                   l_act_budgets_rec.requester_id := l_offer_owner;
3199                   l_act_budgets_rec.approver_id :=
3200                                                ozf_utility_pvt.get_resource_id (fnd_global.user_id);
3201               -- when workflow goes through without approval, fnd_global.user_id is not passed.
3202                   IF l_act_budgets_rec.approver_id = -1 THEN
3203                      l_act_budgets_rec.approver_id := l_offer_owner;
3204                   END IF;
3205                   l_act_budgets_rec.justification :=
3206                                              fnd_message.get_string ('OZF', 'OZF_ACT_BUDGET_LUMPSUM_UTIL');
3207                   l_act_budgets_rec.parent_source_id := l_prod_budget_rec.fund_id;
3208                   l_act_budgets_rec.parent_src_curr := l_prod_budget_rec.currency_code;
3209                   l_act_budgets_rec.parent_src_apprvd_amt := l_converted_amt; -- in budget currency.
3210                   l_act_util_rec.product_id := l_itemId_tbl(i) ;
3211                   l_act_util_rec.product_level_type := l_levelType_tbl(i);
3212                   l_act_util_rec.gl_date := sysdate;
3213                   --nirprasa,12.2
3214                   l_act_util_rec.plan_currency_code := l_currency_code;
3215                   l_act_util_rec.fund_request_currency_code := l_currency_code;
3216                   --nirprasa,12.2
3217                   l_org_id := find_org_id (l_act_budgets_rec.parent_source_id);
3218                   -- set org_context since workflow mailer does not set the context
3219                   set_org_ctx (l_org_id);
3220 
3221                   process_act_budgets(x_return_status  => l_return_status,
3222                                        x_msg_count => x_msg_count,
3223                                        x_msg_data   => x_msg_data,
3224                                        p_act_budgets_rec => l_act_budgets_rec,
3225                                        p_act_util_rec   =>l_act_util_rec,
3226                                        x_act_budget_id  => l_act_budget_id
3227                                        ) ;
3228                   IF G_DEBUG THEN
3229                     ozf_utility_pvt.debug_message (   l_full_name
3230                                               || ': end create act budgets  ');
3231                   END IF;
3232 
3233                   IF l_return_status = fnd_api.g_ret_sts_error THEN
3234                      RAISE fnd_api.g_exc_error;
3235                   ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
3236                      RAISE fnd_api.g_exc_unexpected_error;
3237                   END IF;
3238                END IF; -- for util amount
3239 
3240                l_act_util_rec             := NULL;
3241                l_act_budgets_rec          := NULL;
3242 
3243             END LOOP;--end for loop
3244 
3245          END LOOP;
3246 
3247 	EXIT WHEN c_off_products%NOTFOUND;  -- AMITAMKU Fix for Bug 14180155 , Added Exit condition for the loop
3248 
3249        END LOOP;   -- AMITAMKU Fix for Bug 14180155 , End of LOOP for l_limit_row check
3250 
3251          CLOSE c_off_products;
3252       END IF;
3253 
3254       --//ER 13333298
3255       IF G_TPM_PROCESS_ENABLED = 'Y' THEN
3256          l_item_key	  := 'ACCRUAL_INFO' || TO_CHAR(SYSDATE,'DDMMRRRRHH24MISS');
3257          l_parameter_list := WF_PARAMETER_LIST_T();
3258 
3259          l_offer_data := DBMS_XMLGEN.getXml('SELECT ''OFFR'' AccrualType,
3260 						    util.utilization_id UtilizationId,
3261 						    util.plan_id PromotionId,
3262 						    util.fund_id FundId,
3263 						    NVL(map.xref_line_id_value,line.activity_product_id) DiscountLineId,
3264 						    util.product_id ProductId,
3265 						    util.cust_account_id CustomerId,
3266 						    util.plan_curr_amount AccrualAmount,
3267 						    ''0'' ShippedQuantity,
3268 						    util.plan_curr_amount Revenue
3269 					     FROM   ozf_funds_utilized_all_b util, ams_act_products line,
3270 						    ozf_xref_map map
3271 					     WHERE  util.product_id = line.inventory_item_id
3272 					       AND  util.plan_type = ''OFFR''
3273 					       AND  util.plan_id = line.act_product_used_by_id
3274 					       AND  line.arc_act_product_used_by = ''OFFR''
3275 					       AND  util.gl_posted_flag = ''Y''
3276 					       AND  line.activity_product_id = map.list_line_id(+)
3277 					       AND  line.act_product_used_by_id = ' || p_offer_id, 0);
3278 
3279 	l_event_name :=  'oracle.apps.ozf.order.accrual.info';
3280 
3281 	 wf_event.raise(p_event_name => l_event_name,
3282 			p_event_key  => l_item_key,
3283 			p_event_data => l_offer_data,
3284 			p_parameters => l_parameter_list,
3285 			p_send_date  => sysdate);
3286 
3287       END IF;
3288 
3289        fnd_msg_pub.count_and_get (
3290          p_encoded=> fnd_api.g_false
3291         ,p_count=> x_msg_count
3292         ,p_data=> x_msg_data
3293       );
3294       IF G_DEBUG THEN
3295          ozf_utility_pvt.debug_message (   l_full_name || ': end');
3296       END IF;
3297   EXCEPTION
3298       WHEN fnd_api.g_exc_error THEN
3299          ROLLBACK TO Posting_lumpsum_amount;
3300          x_return_status            := fnd_api.g_ret_sts_error;
3301          fnd_msg_pub.count_and_get (
3302             p_count=> x_msg_count
3303            ,p_data=> x_msg_data
3304            ,p_encoded=> fnd_api.g_false
3305          );
3306       WHEN fnd_api.g_exc_unexpected_error THEN
3307          ROLLBACK TO Posting_lumpsum_amount;
3308          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3309          fnd_msg_pub.count_and_get (
3310             p_count=> x_msg_count
3311            ,p_data=> x_msg_data
3312            ,p_encoded=> fnd_api.g_false
3313          );
3314       WHEN OTHERS THEN
3315          ROLLBACK TO Posting_lumpsum_amount;
3316          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3317 
3318          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3319             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
3320          END IF;
3321 
3322          fnd_msg_pub.count_and_get (
3323             p_count=> x_msg_count
3324            ,p_data=> x_msg_data
3325            ,p_encoded=> fnd_api.g_false
3326          );
3327      END post_lumpsum_amount;
3328 ---------------------------------------------------------------------
3329 -- PROCEDURE
3330 --    post_utilized_budget
3331 --
3332 -- PURPOSE
3333 -- This procedure is called by updating offer API when changing offer status to "ACTIVE'
3334 -- and by post_utilized_budget concurrent program for scan data offer and lump sum offer.
3335 -- It is used to create utilized records when offer start date reaches.
3336 
3337 -- PARAMETERS
3338 --       p_offer_id
3339 --       p_offer_type
3340 --      ,p_api_version     IN       NUMBER
3341 --      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
3342 --      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
3343 --      ,x_msg_count       OUT      NUMBER
3344 --      ,x_msg_data        OUT      VARCHAR2
3345 --      ,x_return_status   OUT      VARCHAR2)
3346 
3347 -- NOTES
3348 -- HISTORY
3349 --    09/24/2002  feliu  Create.
3350 ----------------------------------------------------------------------
3351  PROCEDURE post_utilized_budget (
3352       p_offer_id        IN       NUMBER
3353      ,p_offer_type      IN       VARCHAR2
3354      ,p_api_version     IN       NUMBER
3355      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
3356      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
3357      ,p_check_date      IN       VARCHAR2 := fnd_api.g_true -- do date validation
3358      ,x_msg_count       OUT NOCOPY      NUMBER
3359      ,x_msg_data        OUT NOCOPY      VARCHAR2
3360      ,x_return_status   OUT NOCOPY      VARCHAR2
3361    ) IS
3362       l_api_version           NUMBER                                  := 1.0;
3363       l_return_status         VARCHAR2 (1)                            := fnd_api.g_ret_sts_success;
3364       l_msg_data               VARCHAR2 (2000);
3365       l_msg_count              NUMBER;
3366       l_api_name              VARCHAR2 (60)                           := 'post_utilized_budget';
3367       l_full_name        CONSTANT VARCHAR2 (90)                           :=    g_pkg_name
3368                                                                              || '.'
3369                                                                              || l_api_name;
3370 
3371       l_cust_setup           NUMBER;
3372       CURSOR c_offer_rec(p_offer_id IN NUMBER) IS
3373          SELECT custom_setup_id
3374          FROM ozf_offers
3375          WHERE qp_list_header_id = p_offer_id;
3376 
3377     BEGIN
3378       SAVEPOINT post_utilized_budget;
3379       IF G_DEBUG THEN
3380          ozf_utility_pvt.debug_message (': begin ' || l_full_name);
3381       END IF;
3382       x_return_status            := fnd_api.g_ret_sts_success;
3383 
3384       IF fnd_api.to_boolean (p_init_msg_list) THEN
3385          fnd_msg_pub.initialize;
3386       END IF;
3387 
3388       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
3389          RAISE fnd_api.g_exc_unexpected_error;
3390       END IF;
3391 
3392       IF p_offer_type = 'SCAN_DATA' THEN
3393            Post_scan_data_amount
3394        (
3395              p_offer_id         => p_offer_id
3396             ,p_api_version     => l_api_version
3397             ,p_init_msg_list   => fnd_api.g_false
3398             ,p_commit          => fnd_api.g_false
3399             ,p_check_date      => p_check_date
3400             ,x_msg_count       => l_msg_count
3401             ,x_msg_data        => l_msg_data
3402             ,x_return_status   => l_return_status
3403           );
3404       ELSIF p_offer_type = 'LUMPSUM' THEN
3405          OPEN c_offer_rec (p_offer_id);
3406          FETCH c_offer_rec INTO l_cust_setup;
3407          CLOSE c_offer_rec;
3408 
3409      IF l_cust_setup = 110 THEN  -- for soft fund.
3410            post_sf_lumpsum_amount
3411            (
3412              p_offer_id         => p_offer_id
3413             ,p_api_version     => l_api_version
3414             ,p_init_msg_list   => fnd_api.g_false
3415             ,p_commit          => fnd_api.g_false
3416             ,p_validation_level => fnd_api.g_valid_level_full
3417             ,x_msg_count       => l_msg_count
3418             ,x_msg_data        => l_msg_data
3419             ,x_return_status   => l_return_status
3420            );
3421      ELSE
3422            post_lumpsum_amount
3423            (
3424              p_offer_id         => p_offer_id
3425             ,p_api_version     => l_api_version
3426             ,p_init_msg_list   => fnd_api.g_false
3427             ,p_commit          => fnd_api.g_false
3428             ,p_check_date      => p_check_date
3429             ,x_msg_count       => l_msg_count
3430             ,x_msg_data        => l_msg_data
3431             ,x_return_status   => l_return_status
3432            );
3433          END IF;
3434 
3435      END IF;
3436 
3437      IF l_return_status <> fnd_api.g_ret_sts_success THEN
3438          x_return_status            := fnd_api.g_ret_sts_error;
3439          RAISE fnd_api.g_exc_error;
3440      END IF;
3441 
3442       fnd_msg_pub.count_and_get (
3443          p_encoded=> fnd_api.g_false
3444         ,p_count=> x_msg_count
3445         ,p_data=> x_msg_data
3446       );
3447 
3448       IF G_DEBUG THEN
3449          ozf_utility_pvt.debug_message (   l_full_name || ': end');
3450       END IF;
3451    EXCEPTION
3452       WHEN fnd_api.g_exc_error THEN
3453          ROLLBACK TO post_utilized_budget;
3454          x_return_status            := fnd_api.g_ret_sts_error;
3455          fnd_msg_pub.count_and_get (
3456             p_count=> x_msg_count
3457            ,p_data=> x_msg_data
3458            ,p_encoded=> fnd_api.g_false
3459          );
3460       WHEN fnd_api.g_exc_unexpected_error THEN
3461          ROLLBACK TO post_utilized_budget;
3462          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3463          fnd_msg_pub.count_and_get (
3464             p_count=> x_msg_count
3465            ,p_data=> x_msg_data
3466            ,p_encoded=> fnd_api.g_false
3467          );
3468       WHEN OTHERS THEN
3469          ROLLBACK TO post_utilized_budget;
3470          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3471 
3472          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3473             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
3474          END IF;
3475 
3476          fnd_msg_pub.count_and_get (
3477             p_count=> x_msg_count
3478            ,p_data=> x_msg_data
3479            ,p_encoded=> fnd_api.g_false
3480          );
3481 
3482   END post_utilized_budget;
3483 
3484 ---------------------------------------------------------------------
3485 -- PROCEDURE
3486 --    adjust_utilized_budget
3487 --
3488 -- PURPOSE
3489 --This API will be called by claim to automatic increase committed and utilized budget
3490 --when automatic adjustment is allowed for scan data offer.
3491 --It will increase both committed and utilized amount.
3492 
3493 -- PARAMETERS
3494 --       p_offer_id
3495 --       p_product_activity_id
3496 --       p_amount
3497 --      ,p_cust_acct_id         IN         NUMBER
3498 --      ,p_bill_to_cust_acct_id IN         NUMBER
3499 --      ,p_bill_to_site_use_id  IN         NUMBER
3500 --      ,p_ship_to_site_use_id  IN         NUMBER
3501 --      ,p_api_version     IN       NUMBER
3502 --      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
3503 --      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
3504 --      ,x_msg_count       OUT      NUMBER
3505 --      ,x_msg_data        OUT      VARCHAR2
3506 --      ,x_return_status   OUT      VARCHAR2)
3507 
3508 -- NOTES
3509 -- HISTORY
3510 --    09/24/2002  feliu  Create.
3511 --    03/29/2005  kdass  bug 5117557 - added params p_cust_acct_id, p_bill_to_cust_acct_id,
3512 --                       p_bill_to_site_use_id, p_ship_to_site_use_id
3513 ----------------------------------------------------------------------
3514 
3515 PROCEDURE  adjust_utilized_budget (
3516       p_claim_id             IN         NUMBER
3517      ,p_offer_id             IN         NUMBER
3518      ,p_product_activity_id  IN         NUMBER
3519      ,p_amount               IN         NUMBER
3520      ,p_cust_acct_id         IN         NUMBER
3521      ,p_bill_to_cust_acct_id IN         NUMBER
3522      ,p_bill_to_site_use_id  IN         NUMBER
3523      ,p_ship_to_site_use_id  IN         NUMBER
3524      ,p_api_version          IN         NUMBER
3525      ,p_init_msg_list        IN         VARCHAR2 := fnd_api.g_false
3526      ,p_commit               IN         VARCHAR2 := fnd_api.g_false
3527      ,x_msg_count            OUT NOCOPY NUMBER
3528      ,x_msg_data             OUT NOCOPY VARCHAR2
3529      ,x_return_status        OUT NOCOPY VARCHAR2
3530    ) IS
3531 
3532       l_return_status             VARCHAR2 (10)                           := fnd_api.g_ret_sts_success;
3533       l_api_name         CONSTANT VARCHAR2 (30)                           := 'adjust_utilized_budget';
3534       l_api_version      CONSTANT NUMBER                                  := 1.0;
3535       l_msg_data               VARCHAR2 (2000);
3536       l_msg_count              NUMBER;
3537       l_full_name        CONSTANT VARCHAR2 (90)                           :=    g_pkg_name
3538                                                                              || '.'
3539                                                                              || l_api_name;
3540       l_amount                    NUMBER                                  := 0;
3541       l_fund_id                   NUMBER;
3542       L_scan_value                NUMBER;
3543       l_available_amt       NUMBER;
3544       l_offer_currency_code       VARCHAR2 (30);
3545       l_product_id                NUMBER;
3546       l_level_type_code         VARCHAR2 (30);
3547       l_act_budgets_rec           ozf_actbudgets_pvt.act_budgets_rec_type;
3548       l_act_util_rec          ozf_actbudgets_pvt.act_util_rec_type ;
3549       l_converted_amt             NUMBER;
3550       l_budget_currency_code             VARCHAR2 (30);
3551       l_act_budget_id             NUMBER;
3552       l_source_from_parent        VARCHAR2 (1);
3553       l_committed_remaining       NUMBER;
3554       l_campaign_id               NUMBER;
3555       l_unit_remaining            NUMBER;
3556       l_util_amount               NUMBER;
3557       l_amount_remaining          NUMBER;
3558       l_cust_acct_id              NUMBER;
3559       l_offer_quantity            NUMBER;
3560 
3561       --get product information.
3562       CURSOR c_off_products (p_product_activity_id IN NUMBER) IS
3563          SELECT DECODE (level_type_code, 'PRODUCT', inventory_item_id, category_id) product_id
3564                ,level_type_code,scan_value, quantity
3565          FROM ams_act_products
3566          WHERE activity_product_Id = p_product_activity_id;
3567 
3568       --get offer currency and source_from_parent
3569       CURSOR c_offer_data(p_qp_list_header_id IN NUMBER) IS
3570          SELECT nvl(transaction_currency_code,fund_request_curr_code),NVL(source_from_parent,'N'),qualifier_id
3571          FROM ozf_offers
3572          WHERE qp_list_header_id = p_qp_list_header_id;
3573 
3574       --get total committed remaining.
3575       ---Ribha commented this. Dont use ozf_object_checkbook_v (non mergeable view)
3576       -- Ribha: use ozf_object_fund_summary instead of ozf_object_checkbook_v
3577       CURSOR c_budget_committed(p_qp_list_header_id IN NUMBER) IS
3578          SELECT SUM(NVL(plan_curr_committed_amt,0) - NVL(plan_curr_utilized_amt,0))
3579          from ozf_object_fund_summary
3580          WHERE object_type = 'OFFR'
3581          AND object_id = p_qp_list_header_id;
3582 
3583        -- get parent campaign id
3584       CURSOR c_parent_camapign(p_qp_list_header_id IN NUMBER) IS
3585          SELECT act_offer_used_by_id
3586          FROM ozf_act_offers
3587          WHERE qp_list_header_id = p_qp_list_header_id
3588          AND arc_act_offer_used_by = 'CAMP';
3589 
3590       --get utilized budget information.
3591       CURSOR c_utilized_budget(p_product_activity_id IN NUMBER) IS
3592          SELECT  fund_id,plan_type,plan_id, currency_code
3593          FROM ozf_funds_utilized_all_b
3594          WHERE activity_product_Id = p_product_activity_id;
3595 
3596       --get total available budget amount.
3597       /*
3598       CURSOR c_budget_data(p_fund_id IN NUMBER) IS
3599          SELECT available_budget,fund_id,currency_code_tc
3600          FROM ozf_fund_details_v
3601          WHERE fund_id = p_fund_id;
3602       */
3603       --12/08/2005 kdass - sql repository fix SQL ID 14892491 - query the base table directly
3604       CURSOR c_budget_data(p_fund_id IN NUMBER) IS
3605          SELECT (NVL(original_budget, 0) - NVL(holdback_amt, 0)
3606                  + NVL(transfered_in_amt, 0) - NVL(transfered_out_amt, 0)) available_budget,
3607                 fund_id,currency_code_tc
3608          FROM ozf_funds_all_b
3609          WHERE fund_id = p_fund_id;
3610 
3611 
3612       --get un_utilized budget.
3613       CURSOR c_source_fund(p_qp_list_header_id IN NUMBER) IS
3614         SELECT fund_id
3615                ,fund_currency
3616                ,NVL(committed_amt,0)-NVL(utilized_amt,0) committed_amt
3617         FROM ozf_object_fund_summary
3618         WHERE object_id =p_qp_list_header_id
3619         AND object_type = 'OFFR';
3620 
3621      /*
3622          SELECT   fund_id
3623                  ,fund_currency
3624                  ,SUM (amount) committed_amt
3625              FROM (SELECT   a1.fund_id fund_id
3626                            ,a1.currency_code fund_currency
3627                            ,NVL (SUM (a1.amount), 0) amount
3628                        FROM ozf_funds_utilized_all_b a1
3629                       WHERE a1.component_id = p_qp_list_header_id
3630                         AND a1.component_type = 'OFFR'
3631                         AND a1.utilization_type = 'REQUEST'
3632                    GROUP BY a1.fund_id, a1.currency_code
3633                    UNION
3634                    SELECT   a2.fund_id fund_id
3635                            ,a2.currency_code fund_currency
3636                            ,-NVL (SUM (a2.amount), 0) amount
3637                        FROM ozf_funds_utilized_all_b a2
3638                       WHERE a2.plan_id = p_qp_list_header_id
3639                         AND a2.plan_type = 'OFFR'
3640                    GROUP BY a2.fund_id, a2.currency_code)
3641          GROUP BY fund_id, fund_currency
3642          ORDER BY fund_id;
3643 */
3644    BEGIN
3645       SAVEPOINT adjust_utilized_budget;
3646       IF G_DEBUG THEN
3647          ozf_utility_pvt.debug_message (   l_full_name || ': start');
3648       END IF;
3649       x_return_status            := fnd_api.g_ret_sts_success;
3650 
3651       IF fnd_api.to_boolean (p_init_msg_list) THEN
3652          fnd_msg_pub.initialize;
3653       END IF;
3654 
3655       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
3656          RAISE fnd_api.g_exc_unexpected_error;
3657       END IF;
3658 
3659       -- get product information.
3660       OPEN c_off_products(p_product_activity_id);
3661       FETCH c_off_products INTO l_product_id, l_level_type_code,l_scan_value,l_offer_quantity;
3662       CLOSE c_off_products;
3663 
3664       -- get offer information.
3665       OPEN c_offer_data(p_offer_id);
3666       FETCH c_offer_data INTO l_offer_currency_code,l_source_from_parent,l_cust_acct_id;
3667       CLOSE c_offer_data;
3668 
3669       l_amount := ozf_utility_pvt.currround(p_amount * l_scan_value ,l_offer_currency_code); -- ninarasi fix for bug 14089950
3670 
3671       IF G_DEBUG THEN
3672          ozf_utility_pvt.debug_message ( l_full_name || 'l_amount:  ' || l_amount);
3673       END IF;
3674       -- get committed remaining. Ribha: changed as performance fix.
3675       OPEN c_budget_committed(p_offer_id);
3676       FETCH c_budget_committed INTO l_committed_remaining;
3677       CLOSE c_budget_committed;
3678     --  l_committed_remaining := nvl(ozf_utility_pvt.get_commited_amount(p_offer_id),0) - nvl(ozf_utility_pvt.get_utilized_amount(p_offer_id),0);
3679 
3680       IF G_DEBUG THEN
3681          ozf_utility_pvt.debug_message (l_full_name ||'l_committed_remaining:  ' || l_committed_remaining);
3682       END IF;
3683 
3684       IF ROUND(l_committed_remaining/l_scan_value) < p_amount THEN -- committed remaining is not enough.
3685          IF l_source_from_parent ='Y' THEN -- offer is sourced from campaign.
3686 
3687          -- get campaign information.
3688             OPEN c_parent_camapign(p_offer_id);
3689             FETCH c_parent_camapign INTO l_campaign_id;
3690             CLOSE c_parent_camapign;
3691 
3692           IF G_DEBUG THEN
3693             ozf_utility_pvt.debug_message (l_full_name ||'create_act_budgets:  ' || l_campaign_id);
3694           END IF;
3695 
3696             l_act_budgets_rec.budget_source_type := 'CAMP';
3697             l_act_budgets_rec.budget_source_id := l_campaign_id;
3698          ELSE  -- sourced from budget.
3699             --find first budget which has enough fund to source requirement.
3700             FOR l_budget_util_rec IN c_utilized_budget (p_product_activity_id) LOOP
3701           --change later if a error has to be raised or not.
3702          /* IF c_utilized_budget%NOTFOUND THEN
3703               ozf_utility_pvt.error_message ('OZF_ACT_BUDG_UTIL_OVER');
3704           END IF;
3705          */
3706                EXIT WHEN c_utilized_budget%NOTFOUND;
3707 
3708                OPEN c_budget_data(l_budget_util_rec.fund_id);
3709                FETCH c_budget_data INTO l_available_amt,l_fund_id,l_budget_currency_code;
3710                CLOSE c_budget_data;
3711 
3712             -- convert the object currency amount in to fund currency
3713                IF l_budget_util_rec.currency_code = l_offer_currency_code THEN
3714                   l_converted_amt            := l_amount - l_committed_remaining;
3715                ELSE
3716 
3717              -- call the currency conversion wrapper
3718                  ozf_utility_pvt.convert_currency (
3719                      x_return_status=> x_return_status
3720                     ,p_from_currency=> l_offer_currency_code
3721                     ,p_to_currency=> l_budget_util_rec.currency_code
3722                     ,p_from_amount=> l_amount - l_committed_remaining
3723                     ,x_to_amount=> l_converted_amt
3724                  );
3725 
3726                  IF x_return_status <> fnd_api.g_ret_sts_success THEN
3727                     x_return_status            := fnd_api.g_ret_sts_error;
3728                     RAISE fnd_api.g_exc_error;
3729                  END IF;
3730                END IF; -- end for currency test.
3731 
3732               --if budget has enough available, then select this budget as source.
3733                EXIT WHEN  l_available_amt >= l_converted_amt;
3734             END LOOP;
3735 
3736             l_act_budgets_rec.budget_source_type := 'FUND';
3737             l_act_budgets_rec.budget_source_id := l_fund_id;
3738 
3739          --handle case for all budgets has not enough money.
3740             IF l_converted_amt > l_available_amt THEN
3741                 ozf_utility_pvt.error_message ('OZF_ACT_BUDG_NO_MONEY');
3742             END IF;
3743 
3744          END IF; -- end of  source from parent.
3745 
3746          l_act_budgets_rec.act_budget_used_by_id := p_offer_id;
3747          l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3748          l_act_budgets_rec.transfer_type := 'REQUEST';
3749          l_act_util_rec.adjustment_type := 'INCREASE_COMM_EARNED';
3750          l_act_util_rec.adjustment_type_id := -8;
3751          l_act_util_rec.adjustment_date := sysdate;
3752          l_act_budgets_rec.request_amount := (p_amount - ROUND(l_committed_remaining/l_scan_value))*l_scan_value; -- in object currency.
3753          l_act_budgets_rec.request_currency := l_offer_currency_code;
3754          l_act_budgets_rec.approved_amount := l_act_budgets_rec.request_amount;
3755          l_act_budgets_rec.approved_original_amount := l_converted_amt; -- in budget currency.
3756          l_act_budgets_rec.approved_in_currency := l_budget_currency_code;
3757          l_act_budgets_rec.status_code := 'APPROVED';
3758          l_act_budgets_rec.request_date := SYSDATE;
3759          l_act_budgets_rec.user_status_id :=
3760                                          ozf_utility_pvt.get_default_user_status (
3761                                              'OZF_BUDGETSOURCE_STATUS'
3762                                              ,l_act_budgets_rec.status_code
3763                                             );
3764          l_act_budgets_rec.approval_date := SYSDATE;
3765          l_act_budgets_rec.approver_id :=  ozf_utility_pvt.get_resource_id (fnd_global.user_id);
3766          l_act_budgets_rec.requester_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
3767 
3768 
3769          ozf_actbudgets_pvt.create_act_budgets (
3770            p_api_version=> l_api_version
3771           ,x_return_status=> l_return_status
3772           ,x_msg_count=> l_msg_count
3773           ,x_msg_data=> l_msg_data
3774           ,p_act_budgets_rec=> l_act_budgets_rec
3775           ,p_act_util_rec=> l_act_util_rec
3776           ,x_act_budget_id=> l_act_budget_id
3777           ,p_approval_flag=> fnd_api.g_true
3778          );
3779 
3780          IF NOT (l_return_status = fnd_api.g_ret_sts_success) THEN
3781              ROLLBACK TO recal_comm_fund_conc;
3782              fnd_msg_pub.count_and_get (
3783               p_count=> x_msg_count
3784              ,p_data=> x_msg_data
3785              ,p_encoded=> fnd_api.g_false
3786              );
3787          END IF;
3788 
3789       END IF ; -- end of committed remaining is less than  required.
3790 
3791       l_unit_remaining := p_amount;
3792 
3793     --Created utilized record.
3794       FOR l_fund_rec IN c_source_fund (p_offer_id) LOOP
3795         IF l_fund_rec.committed_amt <> 0 THEN
3796           l_act_budgets_rec := NULL;
3797           l_act_util_rec  := NULL;
3798 
3799           -- convert the object currency amount in to fund currency
3800           IF l_fund_rec.fund_currency = l_offer_currency_code THEN
3801               l_converted_amt            := l_amount; -- in fund currency
3802           ELSE
3803            -- call the currency conversion wrapper
3804              ozf_utility_pvt.convert_currency (
3805                  x_return_status=> x_return_status
3806                  ,p_from_currency=> l_offer_currency_code
3807                  ,p_to_currency=> l_fund_rec.fund_currency
3808                  ,p_from_amount=> l_amount
3809                  ,x_to_amount=> l_converted_amt
3810              );
3811 
3812              IF x_return_status <> fnd_api.g_ret_sts_success THEN
3813                  x_return_status            := fnd_api.g_ret_sts_error;
3814                  RAISE fnd_api.g_exc_error;
3815              END IF;
3816           END IF;
3817 
3818           --check against the converted amount but update the amount in parent currency
3819           IF NVL (l_fund_rec.committed_amt, 0) >= NVL (l_converted_amt, 0) THEN
3820              l_util_amount              := l_amount; -- in req currency
3821              l_amount_remaining         :=   l_amount
3822                                                 - l_util_amount; -- in request currency
3823              l_act_budgets_rec.parent_src_apprvd_amt := l_converted_amt;
3824           ELSIF NVL (l_fund_rec.committed_amt, 0) < NVL (l_converted_amt, 0) THEN
3825                   -- call the currency conversion wrapper
3826              ozf_utility_pvt.convert_currency (
3827                      x_return_status=> x_return_status
3828                     ,p_from_currency=> l_fund_rec.fund_currency
3829                     ,p_to_currency=> l_offer_currency_code
3830                     ,p_from_amount=> l_fund_rec.committed_amt
3831                     ,x_to_amount=> l_util_amount
3832              );
3833              l_util_amount := ROUND(l_util_amount/l_scan_value) * l_scan_value;
3834              l_unit_remaining := l_unit_remaining - ROUND(l_util_amount/l_scan_value);
3835              l_amount_remaining         :=   l_amount -  l_util_amount; -- in req currnecy
3836              l_act_budgets_rec.parent_src_apprvd_amt :=  l_util_amount;
3837           END IF;
3838 
3839           l_amount                   := l_amount_remaining; -- in req currency
3840           l_act_budgets_rec.request_amount := l_util_amount;
3841           l_act_budgets_rec.act_budget_used_by_id := p_offer_id;
3842           l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
3843           l_act_budgets_rec.budget_source_type := 'OFFR';
3844           l_act_budgets_rec.budget_source_id := p_offer_id;
3845           l_act_budgets_rec.request_currency := l_offer_currency_code;
3846           l_act_budgets_rec.request_date := SYSDATE;
3847           l_act_budgets_rec.status_code := 'APPROVED';
3848           l_act_budgets_rec.user_status_id := ozf_utility_pvt.get_default_user_status (
3849                                              'OZF_BUDGETSOURCE_STATUS'
3850                                              ,l_act_budgets_rec.status_code
3851                                             );
3852           l_act_budgets_rec.transfer_type := 'UTILIZED';
3853           l_act_budgets_rec.approval_date := SYSDATE;
3854           l_act_budgets_rec.approver_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
3855           fnd_message.set_name ('OZF', 'OZF_ACT_BUDGET_INCR_UTIL');
3856           fnd_message.set_token ('CLAIM_ID', p_claim_id, FALSE);
3857           l_act_budgets_rec.justification := fnd_message.get;
3858           l_act_budgets_rec.parent_source_id := l_fund_rec.fund_id;
3859           l_act_budgets_rec.parent_src_curr := l_fund_rec.fund_currency;
3860           l_act_util_rec.product_id := l_product_id ;
3861           l_act_util_rec.product_level_type := l_level_type_code;
3862           l_act_util_rec.gl_date := sysdate;
3863 
3864           --kdass 29-MAR-2006 bug 5117557
3865           l_act_util_rec.cust_account_id := p_cust_acct_id;
3866           l_act_util_rec.billto_cust_account_id := p_bill_to_cust_acct_id;
3867           l_act_util_rec.bill_to_site_use_id := p_bill_to_site_use_id;
3868           l_act_util_rec.ship_to_site_use_id := p_ship_to_site_use_id;
3869           l_act_util_rec.scan_unit := p_amount * l_offer_quantity;
3870           l_act_util_rec.scan_unit_remaining := p_amount * l_offer_quantity;
3871           --l_act_util_rec.scan_unit := p_amount;
3872           --l_act_util_rec.scan_unit_remaining := p_amount;
3873 
3874           l_act_util_rec.activity_product_id := p_product_activity_id;
3875           --l_act_util_rec.utilization_type :='UTILIZED';
3876           l_act_util_rec.utilization_type :='ADJUSTMENT';
3877           l_act_util_rec.adjustment_type := 'INCREASE_COMM_EARNED';
3878           l_act_util_rec.adjustment_type_id := -8;
3879 	   l_act_util_rec.plan_currency_code := l_offer_currency_code; --ninarasi fix for bug 13792836
3880 	 l_act_util_rec.fund_request_currency_code := l_offer_currency_code;--ninarasi fix for bug 13792836
3881        --   l_act_util_rec.billto_cust_account_id := l_cust_acct_id;
3882 
3883           process_act_budgets (x_return_status  => l_return_status,
3884                                        x_msg_count => x_msg_count,
3885                                        x_msg_data   => x_msg_data,
3886                                        p_act_budgets_rec => l_act_budgets_rec,
3887                                        p_act_util_rec   =>l_act_util_rec,
3888                                        x_act_budget_id  => l_act_budget_id
3889                                        ) ;
3890 
3891           IF l_return_status = fnd_api.g_ret_sts_error THEN
3892              RAISE fnd_api.g_exc_error;
3893           ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
3894              RAISE fnd_api.g_exc_unexpected_error;
3895           END IF;
3896         EXIT WHEN l_amount_remaining = 0;
3897        END IF;
3898       END LOOP;
3899 
3900        fnd_msg_pub.count_and_get (
3901          p_encoded=> fnd_api.g_false
3902         ,p_count=> x_msg_count
3903         ,p_data=> x_msg_data
3904       );
3905       IF G_DEBUG THEN
3906          ozf_utility_pvt.debug_message (   l_full_name
3907                                      || ': end');
3908       END IF;
3909   EXCEPTION
3910       WHEN fnd_api.g_exc_error THEN
3911          ROLLBACK TO adjust_utilized_budget;
3912          x_return_status            := fnd_api.g_ret_sts_error;
3913          fnd_msg_pub.count_and_get (
3914             p_count=> x_msg_count
3915            ,p_data=> x_msg_data
3916            ,p_encoded=> fnd_api.g_false
3917          );
3918       WHEN fnd_api.g_exc_unexpected_error THEN
3919          ROLLBACK TO adjust_utilized_budget;
3920          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3921          fnd_msg_pub.count_and_get (
3922             p_count=> x_msg_count
3923            ,p_data=> x_msg_data
3924            ,p_encoded=> fnd_api.g_false
3925          );
3926       WHEN OTHERS THEN
3927          ROLLBACK TO adjust_utilized_budget;
3928          x_return_status            := fnd_api.g_ret_sts_unexp_error;
3929 
3930          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
3931             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
3932          END IF;
3933 
3934          fnd_msg_pub.count_and_get (
3935             p_count=> x_msg_count
3936            ,p_data=> x_msg_data
3937            ,p_encoded=> fnd_api.g_false
3938          );
3939 
3940     END adjust_utilized_budget;
3941 
3942 /*****************************************************************************************/
3943 -- Start of Comments
3944 -- NAME
3945 --    update_budget_source
3946 -- PURPOSE
3947 -- This API is called from the java layer from the update button on budget_sourcing screen
3948 -- It update source_from_parent column for ams_campaign_schedules_b and AMS_EVENT_OFFERS_ALL_B.
3949 -- HISTORY
3950 -- 12/08/2002  feliu  CREATED
3951 ---------------------------------------------------------------------
3952 
3953    PROCEDURE update_budget_source(
3954       p_object_version_number IN       NUMBER
3955      ,p_budget_used_by_id     IN       NUMBER
3956      ,p_budget_used_by_type   IN       VARCHAR2
3957      ,p_from_parent           IN       VARCHAR2
3958      ,p_api_version           IN       NUMBER
3959      ,p_init_msg_list         IN       VARCHAR2 := fnd_api.g_false
3960      ,p_commit                IN       VARCHAR2 := fnd_api.g_false
3961      ,p_validation_level      IN       NUMBER := fnd_api.g_valid_level_full
3962      ,x_return_status         OUT NOCOPY      VARCHAR2
3963      ,x_msg_count             OUT NOCOPY      NUMBER
3964      ,x_msg_data              OUT NOCOPY      VARCHAR2
3965    ) IS
3966       l_api_version   CONSTANT NUMBER                                  := 1.0;
3967       l_api_name      CONSTANT VARCHAR2 (50)                           := 'update_budget_source';
3968       l_full_name     CONSTANT VARCHAR2 (80)                           :=    g_pkg_name
3969                                                                           || '.'
3970                                                                           || l_api_name;
3971       l_return_status          VARCHAR2 (1);
3972       l_msg_data               VARCHAR2 (10000);
3973       l_msg_count              NUMBER;
3974 
3975 BEGIN
3976       SAVEPOINT update_budget_source;
3977       IF G_DEBUG THEN
3978          ozf_utility_pvt.debug_message (': begin ' || l_full_name);
3979       END IF;
3980       x_return_status            := fnd_api.g_ret_sts_success;
3981 
3982       IF fnd_api.to_boolean (p_init_msg_list) THEN
3983          fnd_msg_pub.initialize;
3984       END IF;
3985 
3986       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
3987          RAISE fnd_api.g_exc_unexpected_error;
3988       END IF;
3989 
3990       IF p_budget_used_by_type = 'CSCH' THEN
3991 
3992          UPDATE ams_campaign_schedules_b
3993          SET source_from_parent = p_from_parent
3994              --,object_version_number =   p_object_version_number + 1
3995          WHERE schedule_id = p_budget_used_by_id;
3996          --AND object_version_number = p_object_version_number;
3997 
3998          IF (SQL%NOTFOUND) THEN
3999          -- Error, check the msg level and added an error message to the
4000          -- API message list
4001             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
4002                fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
4003                fnd_msg_pub.ADD;
4004             END IF;
4005             RAISE fnd_api.g_exc_unexpected_error;
4006          END IF;
4007       ELSE
4008          UPDATE ams_event_offers_all_b
4009          SET source_from_parent = p_from_parent
4010          WHERE event_offer_id = p_budget_used_by_id;
4011 
4012          IF (SQL%NOTFOUND) THEN
4013          -- Error, check the msg level and added an error message to the
4014          -- API message list
4015             IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_error) THEN
4016                fnd_message.set_name ('OZF', 'OZF_API_RECORD_NOT_FOUND');
4017                fnd_msg_pub.ADD;
4018             END IF;
4019             RAISE fnd_api.g_exc_unexpected_error;
4020         END IF;
4021       END IF;
4022 
4023       -- Standard check of p_commit.
4024       IF fnd_api.to_boolean (p_commit) THEN
4025          COMMIT WORK;
4026       END IF;
4027 
4028       fnd_msg_pub.count_and_get (
4029          p_encoded=> fnd_api.g_false
4030         ,p_count=> x_msg_count
4031         ,p_data=> x_msg_data
4032       );
4033 
4034       IF G_DEBUG THEN
4035          ozf_utility_pvt.debug_message (   l_full_name || ': end');
4036       END IF;
4037    EXCEPTION
4038       WHEN fnd_api.g_exc_error THEN
4039          ROLLBACK TO update_budget_source;
4040          x_return_status            := fnd_api.g_ret_sts_error;
4041          fnd_msg_pub.count_and_get (
4042             p_count=> x_msg_count
4043            ,p_data=> x_msg_data
4044            ,p_encoded=> fnd_api.g_false
4045          );
4046       WHEN fnd_api.g_exc_unexpected_error THEN
4047          ROLLBACK TO update_budget_source;
4048          x_return_status            := fnd_api.g_ret_sts_unexp_error;
4049          fnd_msg_pub.count_and_get (
4050             p_count=> x_msg_count
4051            ,p_data=> x_msg_data
4052            ,p_encoded=> fnd_api.g_false
4053          );
4054       WHEN OTHERS THEN
4055          ROLLBACK TO update_budget_source;
4056          x_return_status            := fnd_api.g_ret_sts_unexp_error;
4057 
4058          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
4059             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
4060          END IF;
4061 
4062          fnd_msg_pub.count_and_get (
4063             p_count=> x_msg_count
4064            ,p_data=> x_msg_data
4065            ,p_encoded=> fnd_api.g_false
4066          );
4067    END update_budget_source;
4068 
4069 
4070  /*****************************************************************************************/
4071 -- Start of Comments
4072 -- NAME
4073 --    post_sf_lumpsum_amount
4074 -- PURPOSE
4075 -- This API is called from soft fund request to create expense based utilization.
4076 -- HISTORY
4077 -- 10/22/2003  feliu  CREATED
4078 ---------------------------------------------------------------------
4079 
4080    PROCEDURE post_sf_lumpsum_amount (
4081       p_offer_id        IN       NUMBER
4082      ,p_api_version     IN       NUMBER
4083      ,p_init_msg_list   IN       VARCHAR2 := fnd_api.g_false
4084      ,p_commit          IN       VARCHAR2 := fnd_api.g_false
4085      ,p_validation_level      IN       NUMBER := fnd_api.g_valid_level_full
4086      ,x_msg_count       OUT NOCOPY      NUMBER
4087      ,x_msg_data        OUT NOCOPY      VARCHAR2
4088      ,x_return_status   OUT NOCOPY      VARCHAR2
4089    ) IS
4090       l_return_status             VARCHAR2 (10)                           := fnd_api.g_ret_sts_success;
4091       l_api_name         CONSTANT VARCHAR2 (30)                           := 'post_sf_lumpsum_amount';
4092       l_api_version      CONSTANT NUMBER                                  := 1.0;
4093       l_full_name        CONSTANT VARCHAR2 (90)                           :=    g_pkg_name
4094                                                                              || '.'
4095                                                                              || l_api_name;
4096       l_req_header_id                  NUMBER;
4097       l_offer_id                  NUMBER := p_offer_id;
4098        l_media_id                NUMBER;
4099       l_fund_id                   NUMBER;
4100       l_act_budget_id             NUMBER;
4101       l_act_budgets_rec           ozf_actbudgets_pvt.act_budgets_rec_type;
4102       l_act_util_rec              ozf_actbudgets_pvt.act_util_rec_type ;
4103       l_amount                    NUMBER                                  := 0;
4104       l_converted_amt             NUMBER;
4105       l_level_type_code         VARCHAR2 (30);
4106       l_currency_code             VARCHAR2 (30);
4107       l_total_committed_amt       NUMBER;
4108       l_utilized_amt              NUMBER;
4109       l_cust_acct_id      NUMBER;
4110       l_req_owner              NUMBER;
4111       l_org_id                    NUMBER;
4112       l_offer_org_id                    NUMBER;
4113       --get request date and currency.
4114       CURSOR c_request_date(p_offer_id IN NUMBER) IS
4115         SELECT req.request_header_id, req.currency_code,off.qualifier_id, req.submitted_by,off.org_id --approved_by
4116         FROM ozf_request_headers_all_b req, ozf_offers off
4117         WHERE req.offer_id =p_offer_id
4118         AND req.offer_id = off.qp_list_header_id;
4119 
4120       --get expense information.
4121       CURSOR c_req_expense (p_request_header_id IN NUMBER) IS
4122          select item_id, NVL(approved_amount,0),item_type from ozf_request_lines_all
4123          where request_header_id =p_request_header_id;
4124 
4125       --kdass 08-Jun-2005 Bug 4415878 SQL Repository Fix - changed the cursor query
4126       -- get committed budget information.
4127       CURSOR c_req_budgets (p_offer_id IN NUMBER) IS
4128          SELECT NVL(plan_curr_committed_amt,0) approved_amount
4129                 ,fund_id
4130                 ,fund_currency currency_code
4131          FROM ozf_object_fund_summary
4132          WHERE object_id =p_offer_id
4133          AND object_type = 'OFFR';
4134 
4135          /*
4136          SELECT SUM (approved_amount) approved_amount, fund_id, currency_code
4137          FROM (
4138                SELECT NVL(plan_curr_amount,0) approved_amount, fund_id, currency_code
4139                FROM ozf_funds_utilized_all_b
4140                WHERE utilization_type = 'REQUEST'
4141                AND component_type = 'OFFR'
4142                AND component_id = p_offer_id
4143                UNION ALL
4144                SELECT NVL(-plan_curr_amount,0) approved_amount, fund_id, currency_code
4145                FROM ozf_funds_utilized_all_b
4146                WHERE utilization_type = 'TRANSFER'
4147                AND plan_type = 'OFFR'
4148                AND plan_id = p_offer_id
4149               ) GROUP BY fund_id, currency_code;
4150 
4151 
4152       CURSOR c_req_budgets (p_offer_id IN NUMBER) IS
4153          SELECT SUM(NVL(DECODE(utilization_type, 'REQUEST',util.plan_curr_amount,-util.plan_curr_amount),0)) approved_amount,
4154             util.fund_id,util.currency_code
4155          FROM ozf_funds_utilized_all_b util
4156          WHERE util.utilization_type IN ('REQUEST','TRANSFER')
4157          AND DECODE(util.utilization_type,'REQUEST', util.component_type,util.plan_type) = 'OFFR'
4158          AND DECODE(util.utilization_type,'REQUEST', util.component_id,util.plan_id) = p_offer_id
4159          GROUP BY util.fund_id,util.currency_code;
4160       */
4161 
4162       --kdass 08-Jun-2005 Bug 4415878 SQL Repository Fix - changed the cursor query
4163       -- get total committed and utilized amount
4164       CURSOR c_committed_budgets(p_offer_id IN NUMBER) IS
4165         SELECT SUM(NVL(plan_curr_committed_amt,0))
4166         FROM ozf_object_fund_summary
4167         WHERE object_id =p_offer_id
4168         AND object_type = 'OFFR';
4169 
4170 /*
4171          SELECT SUM (approved_amount)
4172          FROM (SELECT NVL(plan_curr_amount,0) approved_amount
4173                FROM ozf_funds_utilized_all_b
4174                WHERE utilization_type = 'REQUEST'
4175                  AND component_type = 'OFFR'
4176                  AND component_id = p_offer_id
4177                UNION ALL
4178                SELECT NVL(-plan_curr_amount,0) approved_amount
4179                FROM ozf_funds_utilized_all_b
4180                WHERE utilization_type = 'TRANSFER'
4181                  AND plan_type = 'OFFR'
4182                  AND plan_id = p_offer_id);
4183 
4184 
4185       CURSOR c_committed_budgets(p_offer_id IN NUMBER) IS
4186         SELECT SUM(DECODE(utilization_type,'REQUEST',plan_curr_amount,'TRANSFER',-plan_curr_amount))
4187         FROM ozf_funds_utilized_all_b
4188         WHERE utilization_type IN ('REQUEST','TRANSFER')
4189         AND DECODE(utilization_type,'REQUEST', component_type,plan_type) = 'OFFR'
4190         AND DECODE(utilization_type,'REQUEST', component_id,plan_id) = p_offer_id;
4191       */
4192 
4193       -- Added for bug 7030415, get conversion type
4194       CURSOR c_get_conversion_type( p_org_id   IN   NUMBER) IS
4195          SELECT exchange_rate_type
4196          FROM   ozf_sys_parameters_all
4197          WHERE  org_id = p_org_id;
4198 
4199       l_exchange_rate_type VARCHAR2(30) := FND_API.G_MISS_CHAR;
4200       l_rate               NUMBER;
4201 
4202    BEGIN
4203       SAVEPOINT Posting_lumpsum_amount;
4204       IF G_DEBUG THEN
4205          ozf_utility_pvt.debug_message (   l_full_name || ': start');
4206       END IF;
4207       x_return_status            := fnd_api.g_ret_sts_success;
4208 
4209       IF fnd_api.to_boolean (p_init_msg_list) THEN
4210          fnd_msg_pub.initialize;
4211       END IF;
4212 
4213       IF NOT fnd_api.compatible_api_call (l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
4214          RAISE fnd_api.g_exc_unexpected_error;
4215       END IF;
4216 
4217       OPEN c_request_date(l_offer_id);
4218       FETCH c_request_date INTO l_req_header_id,l_currency_code,l_cust_acct_id,l_req_owner,l_offer_org_id;
4219       CLOSE c_request_date;
4220 
4221       -- get total committed amount.
4222       OPEN c_committed_budgets(l_offer_id);
4223       FETCH c_committed_budgets INTO l_total_committed_amt;
4224       CLOSE c_committed_budgets;
4225 
4226 
4227       OPEN c_req_expense (l_req_header_id);
4228 
4229       LOOP
4230         FETCH c_req_expense INTO l_media_id, l_amount, l_level_type_code;
4231 
4232         EXIT WHEN c_req_expense%NOTFOUND;
4233        IF l_amount  <> 0 THEN
4234         FOR l_req_budgets IN c_req_budgets (l_offer_id)
4235             LOOP
4236                -- change later if a error has to be raised or not.
4237              /*  IF c_req_budgets%NOTFOUND THEN
4238                   ozf_utility_pvt.error_message ('OZF_ACT_BUDG_UTIL_OVER');
4239                 END IF;
4240               */
4241                EXIT WHEN c_req_budgets%NOTFOUND;
4242                 l_utilized_amt := ozf_utility_pvt.currround((l_req_budgets.approved_amount / l_total_committed_amt) * l_amount ,l_currency_code);
4243                --l_utilized_amt := ROUND((l_req_budgets.approved_amount / l_total_committed_amt) * l_amount,2);
4244 
4245            IF G_DEBUG THEN
4246               ozf_utility_pvt.debug_message (  ': lumpsum posting amount ' || l_utilized_amt);
4247            END IF;
4248 
4249                -- convert the object currency amount in to fund currency
4250                IF l_req_budgets.currency_code = l_currency_code THEN
4251                   l_converted_amt            := l_utilized_amt;
4252                ELSE
4253                   -- call the currency conversion wrapper
4254                   --Added for bug 7030415
4255 
4256                   OPEN c_get_conversion_type(l_offer_org_id);
4257                   FETCH c_get_conversion_type INTO l_exchange_rate_type;
4258                   CLOSE c_get_conversion_type;
4259 
4260                   ozf_utility_pvt.convert_currency (
4261                      x_return_status=> x_return_status
4262                     ,p_from_currency=> l_currency_code
4263                     ,p_to_currency=> l_req_budgets.currency_code
4264                     ,p_conv_type=> l_exchange_rate_type
4265                     ,p_from_amount=> l_utilized_amt
4266                     ,x_to_amount=> l_converted_amt
4267                     ,x_rate=> l_rate
4268                   );
4269 
4270                   IF x_return_status <> fnd_api.g_ret_sts_success THEN
4271                      x_return_status            := fnd_api.g_ret_sts_error;
4272                      RAISE fnd_api.g_exc_error;
4273                   END IF;
4274                END IF;
4275            IF G_DEBUG THEN
4276               ozf_utility_pvt.debug_message (  ': l_converted_amt ' || l_converted_amt);
4277            END IF;
4278 
4279                IF l_converted_amt <> 0 THEN
4280                   l_act_budgets_rec.request_amount := l_utilized_amt; --in object currency.
4281                   l_act_budgets_rec.act_budget_used_by_id := l_offer_id;
4282                   l_act_budgets_rec.arc_act_budget_used_by := 'OFFR';
4283                   l_act_budgets_rec.budget_source_type := 'OFFR';
4284                   l_act_budgets_rec.budget_source_id := l_offer_id;
4285                   l_act_budgets_rec.request_currency := l_currency_code;
4286                   l_act_budgets_rec.request_date := SYSDATE;
4287                   l_act_budgets_rec.status_code := 'APPROVED';
4288                   l_act_budgets_rec.user_status_id := ozf_utility_pvt.get_default_user_status (
4289                                                               'OZF_BUDGETSOURCE_STATUS'
4290                                                               ,l_act_budgets_rec.status_code
4291                                                               );
4292                   l_act_budgets_rec.transfer_type := 'UTILIZED';
4293                   l_act_budgets_rec.approval_date := SYSDATE;
4294                   l_act_budgets_rec.requester_id := l_req_owner;
4295                   l_act_budgets_rec.approver_id := ozf_utility_pvt.get_resource_id (fnd_global.user_id);
4296               -- when workflow goes through without approval, fnd_global.user_id is not passed.
4297                   IF l_act_budgets_rec.approver_id = -1 THEN
4298                      l_act_budgets_rec.approver_id := l_req_owner;
4299                   END IF;
4300                   l_act_budgets_rec.justification :=
4301                                              fnd_message.get_string ('OZF', 'OZF_SF_BUDGET_LUMPSUM_UTIL');
4302                   l_act_budgets_rec.parent_source_id := l_req_budgets.fund_id;
4303                   l_act_budgets_rec.parent_src_curr := l_req_budgets.currency_code;
4304                   l_act_budgets_rec.parent_src_apprvd_amt := l_converted_amt; -- in budget currency.
4305                   l_act_util_rec.product_id := l_media_id ;
4306                   l_act_util_rec.product_level_type := l_level_type_code;
4307                   l_act_util_rec.gl_date := sysdate;
4308                 --  l_act_util_rec.billto_cust_account_id := l_cust_acct_id;
4309                   l_act_util_rec.reference_id := l_req_header_id;
4310                   l_act_util_rec.reference_type := 'SOFT_FUND';
4311 
4312                   --nirprasa,12.1.1
4313                   l_act_util_rec.plan_currency_code := l_currency_code;
4314                   l_act_util_rec.fund_request_currency_code := l_currency_code;
4315                   --nirprasa,12.1.1
4316                   l_org_id := find_org_id (l_act_budgets_rec.parent_source_id);
4317                   -- set org_context since workflow mailer does not set the context
4318                   set_org_ctx (l_org_id);
4319             IF G_DEBUG THEN
4320               ozf_utility_pvt.debug_message (  ': l_req_owner ' || l_act_budgets_rec.approver_id);
4321            END IF;
4322                 process_act_budgets (x_return_status  => l_return_status,
4323                                        x_msg_count => x_msg_count,
4324                                        x_msg_data   => x_msg_data,
4325                                        p_act_budgets_rec => l_act_budgets_rec,
4326                                        p_act_util_rec   =>l_act_util_rec,
4327                                        x_act_budget_id  => l_act_budget_id
4328                                        ) ;
4329 
4330                   IF l_return_status = fnd_api.g_ret_sts_error THEN
4331                      RAISE fnd_api.g_exc_error;
4332                   ELSIF l_return_status = fnd_api.g_ret_sts_unexp_error THEN
4333                      RAISE fnd_api.g_exc_unexpected_error;
4334                   END IF;
4335                END IF; -- for util amount
4336 
4337                IF G_DEBUG THEN
4338                   ozf_utility_pvt.debug_message (   l_full_name
4339                                               || ': end create act budgets  ');
4340                END IF;
4341                l_act_util_rec             := NULL;
4342                l_act_budgets_rec          := NULL;
4343             END LOOP;
4344            END IF; -- end of l_amount
4345         END LOOP ;
4346 
4347         CLOSE c_req_expense;
4348 
4349 
4350        fnd_msg_pub.count_and_get (
4351          p_encoded=> fnd_api.g_false
4352         ,p_count=> x_msg_count
4353         ,p_data=> x_msg_data
4354       );
4355       IF G_DEBUG THEN
4356          ozf_utility_pvt.debug_message (   l_full_name || ': end');
4357       END IF;
4358   EXCEPTION
4359       WHEN fnd_api.g_exc_error THEN
4360          ROLLBACK TO Posting_lumpsum_amount;
4361          x_return_status            := fnd_api.g_ret_sts_error;
4362          fnd_msg_pub.count_and_get (
4363             p_count=> x_msg_count
4364            ,p_data=> x_msg_data
4365            ,p_encoded=> fnd_api.g_false
4366          );
4367       WHEN fnd_api.g_exc_unexpected_error THEN
4368          ROLLBACK TO Posting_lumpsum_amount;
4369          x_return_status            := fnd_api.g_ret_sts_unexp_error;
4370          fnd_msg_pub.count_and_get (
4371             p_count=> x_msg_count
4372            ,p_data=> x_msg_data
4373            ,p_encoded=> fnd_api.g_false
4374          );
4375       WHEN OTHERS THEN
4376          ROLLBACK TO Posting_lumpsum_amount;
4377          x_return_status            := fnd_api.g_ret_sts_unexp_error;
4378 
4379          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
4380             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
4381          END IF;
4382 
4383          fnd_msg_pub.count_and_get (
4384             p_count=> x_msg_count
4385            ,p_data=> x_msg_data
4386            ,p_encoded=> fnd_api.g_false
4387          );
4388 
4389      END post_sf_lumpsum_amount;
4390 
4391 
4392 
4393    ----------------------------------------------------------------------
4394    PROCEDURE update_request_status (
4395       x_return_status     OUT NOCOPY      VARCHAR2,
4396       x_msg_count         OUT NOCOPY      NUMBER,
4397       x_msg_data          OUT NOCOPY      VARCHAR2,
4398       p_offer_is           IN    NUMBER
4399    ) IS
4400       CURSOR c_req_header_rec(p_offer_id IN NUMBER) IS
4401          SELECT request_header_id,object_version_number,status_code
4402          FROM ozf_request_headers_all_b
4403          WHERE offer_id = p_offer_id;
4404 
4405       l_req_header_id           NUMBER;
4406       l_obj_ver_num             NUMBER;
4407       l_status_code             VARCHAR2 (30);
4408       l_return_status           VARCHAR2 (10)         := fnd_api.g_ret_sts_success;
4409       l_api_name                VARCHAR2 (60)         := 'update_request_status';
4410       l_full_name               VARCHAR2 (100)        := g_pkg_name||'.'||l_api_name;
4411       l_api_version             NUMBER                := 1;
4412    BEGIN
4413 
4414       IF G_DEBUG THEN
4415          ams_utility_pvt.debug_message(l_full_name||' : '||'begin');
4416       END IF;
4417 
4418       OPEN c_req_header_rec (p_offer_is);
4419       FETCH c_req_header_rec INTO l_req_header_id,
4420                                 l_obj_ver_num,
4421                                 l_status_code;
4422       CLOSE c_req_header_rec;
4423 
4424       IF l_status_code <> 'APPROVED' THEN
4425          UPDATE ozf_request_headers_all_b
4426          SET status_code ='APPROVED',
4427              object_version_number = l_obj_ver_num + 1
4428          WHERE request_header_id = l_req_header_id;
4429       END IF;
4430 
4431       fnd_msg_pub.count_and_get (
4432             p_count=> x_msg_count,
4433             p_data=> x_msg_data,
4434             p_encoded=> fnd_api.g_false
4435          );
4436 
4437    EXCEPTION
4438       WHEN fnd_api.g_exc_error THEN
4439          x_return_status := fnd_api.g_ret_sts_error;
4440          fnd_msg_pub.count_and_get (
4441             p_count=> x_msg_count,
4442             p_data=> x_msg_data,
4443             p_encoded=> fnd_api.g_false
4444          );
4445       WHEN fnd_api.g_exc_unexpected_error THEN
4446          x_return_status := fnd_api.g_ret_sts_unexp_error;
4447          fnd_msg_pub.count_and_get (
4448             p_count=> x_msg_count,
4449             p_data=> x_msg_data,
4450             p_encoded=> fnd_api.g_false
4451          );
4452       WHEN OTHERS THEN
4453          x_return_status := fnd_api.g_ret_sts_unexp_error;
4454 
4455          IF fnd_msg_pub.check_msg_level (fnd_msg_pub.g_msg_lvl_unexp_error) THEN
4456             fnd_msg_pub.add_exc_msg (g_pkg_name, l_api_name);
4457          END IF;
4458 
4459          fnd_msg_pub.count_and_get (
4460             p_count=> x_msg_count,
4461             p_data=> x_msg_data,
4462             p_encoded=> fnd_api.g_false
4463          );
4464    END update_request_status;
4465 
4466 END ozf_fund_adjustment_pvt;