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