DBA Data[Home] [Help]

PACKAGE BODY: APPS.ARP_PROCESS_RETURNS

Source


1 PACKAGE BODY ARP_PROCESS_RETURNS  AS
2 /* $Header: ARPRRTNB.pls 120.17 2010/08/04 09:26:42 npanchak ship $ */
3 
4 /*=======================================================================+
5  |  Package Global Constants
6  +=======================================================================*/
7 G_PKG_NAME      CONSTANT VARCHAR2(30)   := 'ARP_PROCESS_RETURNS';
8 
9 /*=======================================================================+
10  |  Package Global Constants
11  +=======================================================================*/
12 PG_DEBUG varchar2(1) := NVL(FND_PROFILE.value('AFLOG_ENABLED'), 'N');
13 g_ccr_receivables_trx_id     NUMBER(15);
14 g_batch_source_id            ra_batch_sources.batch_source_id%type;
15 g_receipt_handling_option    ra_batch_sources.receipt_handling_option%type;
16 g_nccr_receivables_trx_id    NUMBER(15);
17 
18 /*========================================================================
19  | Prototype Declarations Procedures
20  *=======================================================================*/
21 --
22 PROCEDURE check_rec_in_doubt(p_cash_receipt_id IN NUMBER,
23                              x_rec_in_doubt OUT NOCOPY VARCHAR2,
24                              x_rid_reason OUT NOCOPY VARCHAR2,
25                              x_rec_proc_option IN VARCHAR2);
26 --
27 --
28 PROCEDURE get_receipt_amounts (p_cash_receipt_id IN NUMBER,
29                             x_receipt_amount OUT NOCOPY NUMBER,
30                             x_refund_amount  OUT NOCOPY NUMBER,
31 			    x_rec_proc_option IN VARCHAR2);
32 --
33 PROCEDURE add_ra_to_list(p_ra_info  IN app_info_type,
34                          p_ra_rec   IN ar_receivable_applications%rowtype);
35 --
36 PROCEDURE populate_dff_and_gdf(p_ra_rec  IN ar_receivable_applications%rowtype,
37                                x_dff_rec OUT NOCOPY
38                                   ar_receipt_api_pub.attribute_rec_type,
39                                x_gdf_rec OUT NOCOPY
40                                   ar_receipt_api_pub.global_attribute_rec_type);
41 --
42 PROCEDURE fetch_gl_date( p_ra_rec IN ar_receivable_applications%rowtype,
43                          p_gl_date OUT NOCOPY DATE);
44 --
45 PROCEDURE initialize_globals IS
46 BEGIN
47    BEGIN
48       SELECT receivables_trx_id
49       INTO   g_ccr_receivables_trx_id
50       FROM   ar_receivables_trx
51       WHERE  type = 'CCREFUND'
52       AND    status = 'A';
53    EXCEPTION
54       WHEN NO_DATA_FOUND THEN
55          NULL;
56       WHEN OTHERS THEN
57          RAISE;
58    END;
59    BEGIN
60       SELECT receivables_trx_id
61       INTO   g_nccr_receivables_trx_id
62       FROM   ar_receivables_trx
63       WHERE  type = 'CM_REFUND'
64       AND    status = 'A';
65    EXCEPTION
66       WHEN NO_DATA_FOUND THEN
67          NULL;
68       WHEN OTHERS THEN
69          RAISE;
70    END;
71 
72 EXCEPTION
73    WHEN OTHERS THEN
74      RAISE;
75 END initialize_globals;
76 
77 /*========================================================================
78  | Procedure process_invoice_list()
79  |
80  | DESCRIPTION
81  |      Process Invoices from the list prepared by the AutoInvoice
82  |
83  | PSEUDO CODE/LOGIC
84  |
85  | PARAMETERS
86  |
87  |
88  | RETURNS
89  |      nothing
90  |
91  | KNOWN ISSUES
92  |
93  |
94  |
95  | NOTES
96  |
97  |
98  |
99  | MODIFICATION HISTORY
100  | Date                  Author           Description of Changes
101  | 02-Jul-2003           Ramakant Alat    Created
102  |
103  *=======================================================================*/
104 PROCEDURE process_invoice_list AS
105 
106 -- Get info for given Invoice
107 CURSOR c01 (p_customer_trx_id NUMBER) IS
108 SELECT
109       inv.customer_trx_id inv_customer_trx_id,
110       inv.invoice_currency_code,
111       inv.exchange_rate,
112       cmbs.receipt_handling_option,
113       COUNT(DISTINCT invps.payment_schedule_id) ps_count,
114       get_total_cm_amount(inv.customer_trx_id, cm.request_id) cm_amount,
115       get_total_payment_types(inv.customer_trx_id) total_pmt_types,
116       SUM(invps.amount_due_remaining)/
117       COUNT(DISTINCT NVL(adj.adjustment_id, -9.9)) inv_balance,
118       (SUM(NVL(invps.amount_applied, 0))+
119       SUM(NVL(invps.discount_taken_earned, 0)))/
120       COUNT(DISTINCT NVL(adj.adjustment_id, -9.9)) inv_app_amount,
121       NVL(SUM(DECODE(adj.adjustment_type, 'C', adj.amount, 0)), 0) /
122       COUNT(DISTINCT invps.payment_schedule_id) cmt_adj_amount,
123       NVL(SUM(DECODE(adj.adjustment_type, 'C', 0, adj.amount)), 0) /
124       COUNT(DISTINCT invps.payment_schedule_id) adj_amount
125 FROM
126       ra_customer_trx inv,
127       ar_payment_schedules invps,
128       ra_cust_trx_types itt,
129       ra_batch_sources cmbs,
130       ra_customer_trx cm,
131       ar_adjustments adj
132 WHERE
133       inv.customer_trx_id            = cm.previous_customer_trx_id
134   AND inv.customer_trx_id            = p_customer_trx_id
135   AND inv.customer_trx_id            = invps.customer_trx_id
136   AND cm.batch_source_id             = cmbs.batch_source_id
137   AND cm.request_id                  = arp_global.request_id
138   AND inv.cust_trx_type_id           = itt.cust_trx_type_id
139   AND cmbs.receipt_handling_option IS NOT NULL
140   AND itt.allow_overapplication_flag = 'N'
141   AND inv.customer_trx_id            = adj.customer_trx_id (+)
142 GROUP BY
143       cmbs.receipt_handling_option,
144       cm.request_id,
145       inv.invoice_currency_code,
146       inv.exchange_rate,
147       inv.customer_trx_id;
148 /***
149    HAVING
150       (SUM(invps.amount_due_original)/
151        COUNT(DISTINCT NVL(adj.adjustment_id, -9.9))) > 0 ;
152 ***/
153 
154 adj_exception              EXCEPTION;
155 overapp_exception          EXCEPTION;
156 l_total_unapp_amount       NUMBER;
157 l_total_unapp_acctd_amount NUMBER;
158 l_rec_in_doubt             VARCHAR2(1):='N';
159 l_rid_reason               VARCHAR2(2000):= null;
160 l_mult_pmt_types_msg       VARCHAR2(2000):=
161                arp_standard.fnd_message('AR_RID_MULTIPLE_PMT_TYPES');
162 l_min_ref_amt_msg          VARCHAR2(2000):=
163                         arp_standard.fnd_message('AR_RID_OAPP_LT_MIN_REF_AMT');
164 l_split_term_with_bal_msg  VARCHAR2(2000):=
165                arp_standard.fnd_message('AR_RID_SPLIT_TERM_WITH_BAL');
166 l_amt_lt_min_ref_amt_msg   VARCHAR2(2000):=
167                arp_standard.fnd_message('AR_RID_OAPP_LT_MIN_REF_AMT');
168 i                          NUMBER(15):= 0;
169 
170 BEGIN
171    --
172    IF PG_DEBUG in ('Y', 'C') THEN
173       arp_standard.debug('arp_process_returns.process_invoice_list()+ ');
174    END IF;
175    --
176    -- Check if there are any Invoices to process in the list
177    --
178    IF inv_info.COUNT = 0 THEN
179       IF PG_DEBUG in ('Y', 'C') THEN
180          arp_standard.debug('No Invoice in the list to process..');
181       END IF;
182       GOTO after_loop;
183    END IF;
184    --
185    -- Process all Invoices added to the PL/SQL table by AutoInvoice
186    --
187    i := inv_info.FIRST;  -- get subscript of first element
188    --
189    WHILE i IS NOT NULL
190    LOOP
191       --
192       IF PG_DEBUG in ('Y', 'C') THEN
193          arp_standard.debug('INV Customer Trx ID [' || i || ']');
194       END IF;
195       --
196       FOR c01_rec IN c01 (i) LOOP
197          --
198          IF PG_DEBUG in ('Y', 'C') THEN
199             arp_standard.debug('CM count [' || inv_info(i).num_of_cms || ']');
200             arp_standard.debug('Inv Balance [' || c01_rec.inv_balance || ']');
201             arp_standard.debug('PS count [' || c01_rec.ps_count || ']');
202             arp_standard.debug('Inv App Amount [' ||
203                c01_rec.inv_app_amount || ']');
204             arp_standard.debug('Commitment Adj amt [' ||
205                c01_rec.cmt_adj_amount || ']');
206             arp_standard.debug('Adj amt [' || c01_rec.adj_amount || ']');
207             arp_standard.debug('CM amt [' || c01_rec.cm_amount || ']');
208          END IF;
209          --
210          -- If adjustment exists then raise exception ***/
211          --
212          IF c01_rec.adj_amount <> 0 THEN
213             arp_standard.debug('arp_process_returns.process_invoice_list : ' ||
214             'adj_EXCEPTION customer_trx_id <' || c01_rec.inv_customer_trx_id ||
215             '>');
216             RAISE adj_exception;
217          END IF;
218          --
219          -- Calculate Total amount which needs to be unapplied from receipts
220          --
221          l_total_unapp_amount := -1 * (c01_rec.inv_balance
222                                - c01_rec.cmt_adj_amount
223                                + c01_rec.cm_amount);
224          --
225          -- No overapplication, so no unapplication required
226          --
227          IF  c01_rec.cm_amount = 0 THEN
228             GOTO end_loop;
229          END IF;
230          --
231          -- If Total Unapp amount > Applied amount then raise exception
232          --
233          IF l_total_unapp_amount > (c01_rec.inv_app_amount)   THEN
234             arp_standard.debug('arp_process_returns.process_invoice_list : ' ||
235             'overapp_EXCEPTION customer_trx_id <'
236             || c01_rec.inv_customer_trx_id || '>');
237             arp_standard.debug('Inv Balance : <' || c01_rec.inv_balance);
238             arp_standard.debug('Inv App Amount : <' || c01_rec.inv_app_amount);
239             arp_standard.debug('Cmt Adj Amount : <' || c01_rec.cmt_adj_amount);
240             arp_standard.debug('CM Amount : <' || c01_rec.cm_amount);
241             RAISE overapp_exception;
242          END IF;
243 
244          --
245          -- Check if invoice has CC payment then check for receipt
246          -- in doubt scenarios
247          --
248          IF c01_rec.total_pmt_types = 0 THEN
249             --
250             inv_info(i).cc_apps           := FALSE; -- No CC Applications
251             inv_info(i).all_recs_in_doubt := FALSE; -- No receipts in doubt
252             inv_info(i).rid_reason        := null;
253             --
254          ELSIF c01_rec.total_pmt_types = 1 THEN
255             --
256             inv_info(i).cc_apps          := TRUE;  -- CC Applications
257             inv_info(i).all_recs_in_doubt := FALSE; -- No receipts in doubt
258             inv_info(i).rid_reason       := null;
259             --
260 /*         ELSE             --- Greater than 1
261             --
262             inv_info(i).cc_apps           := TRUE; -- No CC Applications
263             --
264             IF c01_rec.receipt_handling_option = 'REFUND' THEN
265                inv_info(i).all_recs_in_doubt := TRUE; -- receipts in doubt
266                inv_info(i).rid_reason        := l_mult_pmt_types_msg;
267 
268             ELSE
269                inv_info(i).all_recs_in_doubt := FALSE; -- No receipts in doubt
270                inv_info(i).rid_reason        := null;
271             END IF; -- receipt handling option
272 */ -- GGADHAMS  Commented as Refund can be now done for CC and Non CC Receipt
273 
274          ELSIF  c01_rec.receipt_handling_option = 'REFUND' THEN
275             inv_info(i).cc_apps           := TRUE;
276 	    inv_info(i).all_recs_in_doubt := FALSE; -- No receipts in doubt
277             inv_info(i).rid_reason        := null;
278          ELSE
279             inv_info(i).cc_apps           := TRUE;
280             --
281             --
282          END IF; -- total_pmt_types
283          --
284          -- Check for RID due to min refund amount check
285          --
286          IF c01_rec.receipt_handling_option = 'REFUND' AND
287             inv_info(i).cc_apps AND
288             NOT inv_info(i).all_recs_in_doubt THEN
289             --
290             -- Get functional unapply amount
291             --
292             IF arp_global.functional_currency <> c01_rec.invoice_currency_code
293             THEN
294                l_total_unapp_acctd_amount:= ARPCURR.functional_amount(
295                                           amount=>l_total_unapp_amount,
296                                           currency_code=>
297                                           c01_rec.invoice_currency_code,
298                                           exchange_rate=>c01_rec.exchange_rate,
299                                           precision=>null,
300                                           min_acc_unit=>null);
301             ELSE
302                l_total_unapp_acctd_amount:= l_total_unapp_amount;
303             END IF; -- functional_currency
304             --
305             -- Check for open split term  invoices
306             --
307             IF c01_rec.ps_count > 1  AND c01_rec.inv_balance > 0 THEN
308                --
309                inv_info(i).all_recs_in_doubt := TRUE; -- receipts in doubt
310                inv_info(i).rid_reason        := l_split_term_with_bal_msg;
311                --
312             ELSIF NVL(arp_global.sysparam.min_refund_amount, 0) >
313                   l_total_unapp_acctd_amount THEN
314                --
315                inv_info(i).all_recs_in_doubt := TRUE; -- receipts in doubt
316                inv_info(i).rid_reason        := l_amt_lt_min_ref_amt_msg;
317                --
318             END IF;
319 
320          END IF; -- receipt_handling option
321          --
322          IF PG_DEBUG in ('Y', 'C') THEN
323             arp_standard.debug('Calling unapply_receipts...');
324             arp_standard.debug('Inv Customer Trx ID [' ||
325                c01_rec.inv_customer_trx_id || ']');
326             arp_standard.debug('RecHandOption [' ||
327                c01_rec.receipt_handling_option || ']');
328             arp_standard.debug('Unapp amount [' || l_total_unapp_amount || ']');
329             arp_standard.debug('RID Reason [' || inv_info(i).rid_reason  || ']');
330             IF inv_info(i).all_recs_in_doubt THEN
331                arp_standard.debug('Rec In doubt ');
332             ELSE
333                arp_standard.debug('Rec NOT In doubt ');
334             END IF;
335          END IF;
336 
337          --
338          -- Call unapply_receipts
339          --
340          unapply_receipts (p_inv_customer_trx_id=>c01_rec.inv_customer_trx_id,
341                            p_receipt_handling_option=>
342                            c01_rec.receipt_handling_option);
343 
344          <<end_loop>>
345          NULL;
346       END LOOP;
347       --
348       i := inv_info.NEXT(i);
349       --
350    END LOOP;
351    --
352    <<after_loop>>
353    --
354    IF PG_DEBUG in ('Y', 'C') THEN
355       arp_standard.debug('arp_process_RETURNS.process_invoice_list()- ');
356    END IF;
357 EXCEPTION
358    WHEN OTHERS THEN
359       arp_standard.debug('EXCEPTION : arp_process_returns.process_invoice_list : ' || SQLERRM(SQLCODE));
360       RAISE;
361 END process_invoice_list;
362 
363 /*========================================================================
364  | Procedure process_application_list()
365  |
366  | DESCRIPTION
367  |      Process Applications from the list prepared by the unapply_receipts
368  |
369  | PSEUDO CODE/LOGIC
370  |
371  | PARAMETERS
372  |
373  |
374  | RETURNS
375  |      nothing
376  |
377  | KNOWN ISSUES
378  |
379  |
380  |
381  | NOTES
382  |
383  |
384  |
385  | MODIFICATION HISTORY
386  | Date                  Author           Description of Changes
387  | 18-Jul-2003           Ramakant Alat    Created
388  |
389  *=======================================================================*/
390 PROCEDURE process_application_list AS
391 
392 
393 -- Get open balance for the given Invoice
394 CURSOR c01 (p_payment_schedule_id NUMBER) IS
395 SELECT
396       inv.customer_trx_id inv_customer_trx_id,
397       inv.invoice_currency_code,
398       inv.exchange_rate,
399       invps.amount_due_remaining inv_balance
400 FROM
401       ra_customer_trx inv,
402       ar_payment_schedules invps
403 WHERE
404       invps.payment_schedule_id = p_payment_schedule_id
405   AND inv.customer_trx_id       = invps.customer_trx_id;
406 
407 adj_exception               EXCEPTION;
408 overapp_exception           EXCEPTION;
409 l_apply_failed              EXCEPTION;
410 l_activity_app_failed       EXCEPTION;
411 l_on_account_app_failed     EXCEPTION;
412 l_total_unapp_amount        NUMBER;
413 l_refund_amount             ar_cash_receipts.amount%type;
414 l_pay_refund_amount         ar_cash_receipts.amount%type;
415 l_on_account_amount         ar_cash_receipts.amount%type;
416 l_old_refund_amount         ar_cash_receipts.amount%type;
417 l_receipt_amount            ar_cash_receipts.amount%type;
418 l_reapply_amount            ar_cash_receipts.amount%type;
419 l_new_apply_amount          ar_cash_receipts.amount%type;
420 l_new_apply_amount_fr       ar_cash_receipts.amount%type;
421 l_ch_apply_amount_fr        ar_cash_receipts.amount%type;
422 l_total_unapp_amount        NUMBER;
423 l_rec_in_doubt              VARCHAR2(1):='N';
424 l_rid_reason                VARCHAR2(2000):= null;
425 l_return_status             VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
426 l_msg_count                 NUMBER;
427 l_msg_data                  VARCHAR2(2000);
428 l_app_comments              ar_receivable_applications.comments%type :=
429     arp_standard.fnd_message('AR_RID_PROCESSED_AS_PER_REQ');
430 l_application_ref_type      ar_receivable_applications.application_ref_type%type;
431 l_application_ref_id        ar_receivable_applications.application_ref_id%type;
432 l_application_ref_num       ar_receivable_applications.application_ref_num%type;
433 l_receivable_application_id ar_receivable_applications.receivable_application_id%type;
434 l_new_ra_rec                ar_receivable_applications%rowtype;
435 l_refunding                 BOOLEAN:=FALSE;
436 l_gdf_rec                   ar_receipt_api_pub.global_attribute_rec_type;
437 l_dff_rec                   ar_receipt_api_pub.attribute_rec_type;
438 l_party_id                  hz_parties.party_id%type;
439 BEGIN
440    IF PG_DEBUG in ('Y', 'C') THEN
441       arp_standard.debug('arp_process_returns.process_application_list()+ ');
442    END IF;
443    --
444    -- Check if there are any applications to process in the list
445    --
446    IF app_info.COUNT = 0 THEN
447       IF PG_DEBUG in ('Y', 'C') THEN
448          arp_standard.debug('No Application in the list to process..');
449       END IF;
450       GOTO after_loop;
451    END IF;
452    --
453    -- Process all applications added to the PL/SQL table by unapply_receipts
454    --
455    FOR i IN 1..app_info.COUNT
456    LOOP
457       --
458       --
459       --
460       IF PG_DEBUG in ('Y', 'C') THEN
461          arp_standard.debug('INV Customer Trx ID [' ||
462          app_tab(i).applied_customer_trx_id || ']');
463          arp_standard.debug('rec_proc_option [' ||
464          app_info(i).rec_proc_option || ']');
465          arp_standard.debug('rec_in_doubt [' ||
466          app_info(i).rec_in_doubt || ']');
467          arp_standard.debug('rec_currency_code [' ||
468          app_info(i).rec_currency_code || ']');
469          arp_standard.debug('inv_currency_code [' ||
470          app_info(i).inv_currency_code || ']');
471          arp_standard.debug('rid_reason [' ||
472          app_info(i).rid_reason || ']');
473          arp_standard.debug('trx_number [' ||
474          app_info(i).trx_number || ']');
475       END IF;
476       --
477       FOR c01_rec IN c01 (app_tab(i).applied_payment_schedule_id)
478       LOOP
479          --
480          IF PG_DEBUG in ('Y', 'C') THEN
481             arp_standard.debug('Inv Balance [' || c01_rec.inv_balance || ']');
482             arp_standard.debug('Inv Customer Trx Id [' || c01_rec.inv_customer_trx_id || ']');
483          END IF;
484          --
485          -- Compute reapply amount ** 1 **
486          --
487          l_reapply_amount := LEAST(app_tab(i).amount_applied,
488                                    c01_rec.inv_balance );
489 
490 
491 
492 	 IF PG_DEBUG in ('Y', 'C') THEN
493             arp_standard.debug('  l_reapply_amount  [' ||  l_reapply_amount  || ']');
494          END IF;
495 
496 	 IF l_reapply_amount > 0 THEN
497             --
498             -- Get Amount Applied to be passed to Receipt API
499             --
500             IF app_tab(i).amount_applied +
501                NVL(app_tab(i).earned_discount_taken, 0) >= c01_rec.inv_balance
502             THEN
503             --
504                l_new_apply_amount := null;
505             --
506             ELSE
507             --
508                l_new_apply_amount := app_tab(i).amount_applied;
509             --
510             END IF;
511 
512 	    IF PG_DEBUG in ('Y', 'C') THEN
513             arp_standard.debug('  l_new_apply_amount  [' ||  l_new_apply_amount  || ']');
514             END IF;
515 
516 
517             --
518             -- Populate DFF and GDF for re-app from the Old app
519             --
520             populate_dff_and_gdf(p_ra_rec=>app_tab(i),
521                                  x_dff_rec=>l_dff_rec,
522                                  x_gdf_rec=>l_gdf_rec
523                                  );
524             --
525             -- Apply to original payment schedule
526             --
527             -- Re-apply to the application to the same invoice
528             --
529             IF PG_DEBUG in ('Y', 'C') THEN
530                arp_standard.debug('Re-apply back to invoice ps[' ||
531                   app_tab(i).applied_payment_schedule_id ||'] : <'  ||
532                   l_reapply_amount|| '>');
533             END IF;
534             --
535             --
536             ar_receipt_api_pub.Apply(p_api_version => 1.0,
537                      x_return_status     => l_return_status,
538                      x_msg_count         => l_msg_count,
539                      x_msg_data          => l_msg_data,
540                      p_cash_receipt_id   => app_tab(i).cash_receipt_id,
541                      p_applied_payment_schedule_id  =>
542                          app_tab(i).applied_payment_schedule_id,
543                      p_amount_applied    => l_new_apply_amount,
544                      p_trans_to_receipt_rate =>
545                          app_tab(i).trans_to_receipt_rate,
546                      p_apply_date      => app_tab(i).apply_date,
547                      p_apply_gl_date   => app_tab(i).reversal_gl_date,
548                      p_comments          => app_tab(i).comments,
549                      p_ussgl_transaction_code  =>
550                          app_tab(i).ussgl_transaction_code,
551                      p_customer_trx_line_id  =>
552                          app_tab(i).applied_customer_trx_line_id,
553                      p_attribute_rec  => l_dff_rec,
554                      p_global_attribute_rec  => l_gdf_rec,
555                      p_customer_reference  =>
556                          app_tab(i).customer_reference,
557                      p_customer_reason  => app_tab(i).customer_reason
558                     );
559 
560             IF l_return_status  <> FND_API.G_RET_STS_SUCCESS THEN
561 
562                IF (l_msg_count = 1) THEN
563                   arp_standard.debug('Apply: ' || l_MSG_DATA);
564                ELSIF(l_MSG_COUNT>1)THEN
565                   LOOP
566                      l_MSG_DATA:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_FALSE);
567                      IF (l_MSG_DATA IS NULL)THEN
568                         EXIT;
569                      END IF;
570                      arp_standard.debug('Apply : ' || l_MSG_DATA);
571                   END LOOP;
572                END IF;
573 
574                arp_standard.debug('Apply failed');
575 
576                RAISE l_apply_failed;
577 
578             END IF;
579             --
580             -- Fetch Rec App record for the application
581             --
582             arp_app_pkg.fetch_p(p_ra_id=>
583                    ar_receipt_api_pub.apply_out_rec.receivable_application_id,
584                    p_ra_rec=>l_new_ra_rec);
585             --
586             -- Get Amount Applied from for the new application
587             --
588             l_new_apply_amount_fr := NVL(l_new_ra_rec.amount_applied_from, 0);
589             l_new_apply_amount    := NVL(l_new_ra_rec.amount_applied, 0);
590             --
591          ELSE
592             l_new_apply_amount    := 0;
593             l_new_apply_amount_fr := 0;
594          END IF;
595          --
596          -- Compute change in Application amount applied "from"
597          --
598          IF app_info(i).cross_currency THEN
599             --
600             IF PG_DEBUG in ('Y', 'C') THEN
601                arp_standard.debug('Cross Currency');
602                arp_standard.debug('Re-apply Amount :' || l_reapply_amount);
603                arp_standard.debug('New-apply Amount :' || l_new_apply_amount);
604                arp_standard.debug('T->R Rate       :' ||
605                   app_tab(i).trans_to_receipt_rate);
606                arp_standard.debug('Currency REC    :' ||
607                              app_info(i).rec_currency_code);
608             END IF;
609             --
610             /***
611             l_new_apply_amount_fr :=
612             arp_util.CurrRound(
613                             l_reapply_amount *
614                                app_tab(i).trans_to_receipt_rate,
615                              app_info(i).rec_currency_code
616                             );
617             ***/
618             --
619             l_ch_apply_amount_fr := app_tab(i).amount_applied_from -
620                                        l_new_apply_amount_fr;
621             --
622          ELSE
623             IF PG_DEBUG in ('Y', 'C') THEN
624                arp_standard.debug('Not Cross Currency');
625                arp_standard.debug('Old Amount Applied :' ||
626                   app_tab(i).amount_applied );
627                arp_standard.debug('New Amount Applied :' ||
628                   l_new_apply_amount);
629             END IF;
630             l_ch_apply_amount_fr := app_tab(i).amount_applied -
631                                        l_new_apply_amount;
632          END IF;
633          --
634          IF PG_DEBUG in ('Y', 'C') THEN
635             arp_standard.debug('Change in App amount [' ||
636                app_tab(i).applied_payment_schedule_id ||'] : <'  ||
637                l_ch_apply_amount_fr || '>');
638          END IF;
639          --
640          --
641          --  Initialize amounts
642          --
643          l_refund_amount := 0;
644          l_old_refund_amount := 0;
645          l_on_account_amount := 0;
646          l_receipt_amount := 0;
647          l_refunding := FALSE;
648          l_pay_refund_amount :=0;
649 
650          IF app_info(i).rec_in_doubt = 'N' AND
651          app_info(i).rec_proc_option = 'REFUND' THEN
652             --
653             l_refunding := TRUE;
654             --
655             IF PG_DEBUG in ('Y', 'C') THEN
656                arp_standard.debug('Refunding...');
657             END IF;
658             --
659             -- Get receipt amount and old refund amounts from the receipt
660             --
661             get_receipt_amounts(
662                p_cash_receipt_id=>app_tab(i).cash_receipt_id,
663                x_receipt_amount=>l_receipt_amount,
664                x_refund_amount=>l_old_refund_amount,
665                x_rec_proc_option=> app_info(i).rec_proc_option);
666             --
667             IF PG_DEBUG in ('Y', 'C') THEN
668                arp_standard.debug('Cash Receipt Id ' ||
669                   app_tab(i).cash_receipt_id ||'] :  RecAmt<'  ||
670                   l_receipt_amount|| '>' );
671                arp_standard.debug('Old Refund Amount :[' ||
672                   l_old_refund_amount  ||']');
673             END IF;
674             --
675             --
676             -- Compute refund amount = LEAST(receipt amount - old refunds,
677             --                               change in application amount)
678             --
679             l_refund_amount := LEAST(l_receipt_amount - l_old_refund_amount,
680                                      l_ch_apply_amount_fr);
681             --
682          ELSE
683             l_refund_amount := 0;
684          END IF;
685          --
686          IF PG_DEBUG in ('Y', 'C') THEN
687             arp_standard.debug('New Refund Amount [' || l_refund_amount || ']');
688          END IF;
689 
690 --GGADHAMS Added for Payment Refund
691     IF app_info(i).rec_in_doubt = 'N' AND
692          app_info(i).rec_proc_option = 'PAY_REFUND' THEN
693             --
694             l_refunding := TRUE;
695             --
696             IF PG_DEBUG in ('Y', 'C') THEN
697                arp_standard.debug('Payment Refunding...');
698             END IF;
699             --
700             -- Get receipt amount and old refund amounts from the receipt
701             --
702             get_receipt_amounts(
703                p_cash_receipt_id=>app_tab(i).cash_receipt_id,
704                x_receipt_amount=>l_receipt_amount,
705                x_refund_amount=>l_old_refund_amount,
706        	       x_rec_proc_option=> app_info(i).rec_proc_option);
707             --
708             IF PG_DEBUG in ('Y', 'C') THEN
709                arp_standard.debug('Cash Receipt Id ' ||
710                   app_tab(i).cash_receipt_id ||'] :  RecAmt<'  ||
711                   l_receipt_amount|| '>' );
712                arp_standard.debug('Old Refund Amount :[' ||
713                   l_old_refund_amount  ||']');
714             END IF;
715             --
716             --
717             -- Compute refund amount = LEAST(receipt amount - old refunds,
718             --                               change in application amount)
719             --
720             l_pay_refund_amount := LEAST(l_receipt_amount - l_old_refund_amount,
721                                      l_ch_apply_amount_fr);
722             --
723          ELSE
724             l_pay_refund_amount := 0;
725          END IF;
726          --
727          IF PG_DEBUG in ('Y', 'C') THEN
728             arp_standard.debug('New Payment  Refund Amount [' || l_pay_refund_amount || ']');
729          END IF;
730 --Added till here for Payment Refund
731          --
732 
733          --
734          -- Get On-account application amount = (change in application amount
735          --                                      - refund amount)
736          --
737          l_on_account_amount := l_ch_apply_amount_fr - l_refund_amount - l_pay_refund_amount;
738          --
739          IF PG_DEBUG in ('Y', 'C') THEN
740             arp_standard.debug('On Account Amount [' ||
741                l_on_account_amount|| ']');
742          END IF;
743          --
744          --
745          -- Create Credit Card application
746          --
747          IF l_refund_amount > 0 THEN
748              -- Apply to CCR
749             IF PG_DEBUG in ('Y', 'C') THEN
750                arp_standard.debug('Creating CCR application..');
751                arp_standard.debug('l_app_comments :[' || l_app_comments ||']');
752             END IF;
753             --
754             -- Initialize IN-OUT variables
755             --
756             l_application_ref_type := null;
757             l_application_ref_id   := null;
758             l_application_ref_num  := null;
759             --
760 
761              select party_id
762              into l_party_id
763 	     from
764 	     hz_cust_accounts acc,
765 	     ra_customer_trx  trx
766 	     where trx.bill_to_customer_id = acc.cust_account_id
767              and trx.customer_trx_id  = app_info(i).customer_trx_id; /* bug 9909157 */
768 
769             ar_receipt_api_pub.activity_application(
770                p_api_version                  => 1.0,
771                x_return_status                => l_return_status,
772                x_msg_count                    => l_msg_count,
773                x_msg_data                     => l_msg_data,
774                p_cash_receipt_id              =>
775                   app_tab(i).cash_receipt_id,
776                p_amount_applied               => l_refund_amount,
777                p_applied_payment_schedule_id  => -6,
778                p_receivables_trx_id           => g_ccr_receivables_trx_id,
779                p_apply_gl_date                => app_tab(i).reversal_gl_date,
780                p_comments                     => l_app_comments,
781                p_application_ref_type         => l_application_ref_type,
782                p_application_ref_id           => l_application_ref_id,
783                p_application_ref_num          => l_application_ref_num,
784                p_secondary_application_ref_id =>
785                   app_tab(i).applied_customer_trx_id,
786                p_secondary_app_ref_type       => 'TRANSACTION',
787                p_secondary_app_ref_num        => app_info(i).trx_number,
788                p_receivable_application_id    => l_receivable_application_id,
789                p_party_id                     => l_party_id
790               );
791 
792             IF l_return_status  <> FND_API.G_RET_STS_SUCCESS THEN
793 
794                IF (l_msg_count = 1) THEN
795                   arp_standard.debug('ActivityApp: ' || l_MSG_DATA);
796                ELSIF(l_MSG_COUNT>1)THEN
797                   LOOP
798                      l_MSG_DATA:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_FALSE);
799                      IF (l_MSG_DATA IS NULL)THEN
800                         EXIT;
801                      END IF;
802                      arp_standard.debug('ActivityApp: ' || l_MSG_DATA);
803                   END LOOP;
804                END IF;
805 
806                arp_standard.debug('ActivityApp failed');
807 
808                RAISE l_activity_app_failed;
809             END IF; -- Handle API errors
810             --
811          END IF; -- Process CCR
812          --
813          -- Create On-account application
814          --
815          IF l_on_account_amount > 0 THEN
816          --
817             -- Apply to ON-ACCOUNT
818             IF PG_DEBUG in ('Y', 'C') THEN
819                arp_standard.debug('Creating ON-ACCOUNT application..');
820                arp_standard.debug('l_app_comments :[' || l_app_comments ||']');
821                arp_standard.debug('l_app_comments NVL:[' ||
822                   NVL(app_info(i).rid_reason, l_app_comments) ||']');
823             END IF;
824             --
825             --
826             IF l_refunding  THEN
827                l_app_comments := arp_standard.fnd_message('AR_RID_TOTAL_REFUND_LIMIT');
828             END IF;
829             ar_receipt_api_pub.Apply_on_account(
830                p_api_version                  => 1.0,
831                x_return_status                => l_return_status,
832                x_msg_count                    => l_msg_count,
833                x_msg_data                     => l_msg_data,
834                p_cash_receipt_id              =>
835                   app_tab(i).cash_receipt_id,
836                p_apply_gl_date                => app_tab(i).reversal_gl_date,
837                p_amount_applied               => l_on_account_amount,
838                p_comments                     => NVL(app_info(i).rid_reason,
839                                                      l_app_comments),
840                p_secondary_application_ref_id =>
841                   app_tab(i).applied_customer_trx_id,
842                p_secondary_app_ref_type       => 'TRANSACTION',
843                p_secondary_app_ref_num        => app_info(i).trx_number
844               );
845             IF l_return_status  <> FND_API.G_RET_STS_SUCCESS THEN
846 
847                IF (l_msg_count = 1) THEN
848                   arp_standard.debug('OnaccountApp: ' || l_MSG_DATA);
849                ELSIF(l_MSG_COUNT>1)THEN
850                   LOOP
851                      l_MSG_DATA:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_FALSE);
852                      IF (l_MSG_DATA IS NULL)THEN
853                         EXIT;
854                      END IF;
855                      arp_standard.debug('OnaccountApp : ' || l_MSG_DATA);
856                   END LOOP;
857                END IF;
858 
859                arp_standard.debug('OnaccountApp failed');
860 
861                RAISE l_on_account_app_failed;
862 
863             END IF;
864             --
865          END IF; -- Process On-Account
866 
867 
868          -- GGADHAMS
869          -- Create Payment Refund application
870          --
871          IF l_pay_refund_amount > 0 THEN
872          --
873 
874             -- Initialize IN-OUT variables Bug8402274
875             --
876             l_application_ref_type := null;
877             l_application_ref_id   := null;
878             l_application_ref_num  := null;
879 
880             -- Apply to PAYMENT REFUND
881             IF PG_DEBUG in ('Y', 'C') THEN
882                arp_standard.debug('Creating Payment Refund application..');
883                arp_standard.debug('l_app_comments :[' || l_app_comments ||']');
884                arp_standard.debug('l_app_comments NVL:[' ||
885                   NVL(app_info(i).rid_reason, l_app_comments) ||']');
886             END IF;
887             --
888 		 ar_receipt_api_pub.activity_application(
889                p_api_version                  => 1.0,
890                 p_init_msg_list =>FND_API.G_FALSE,
891                 p_commit =>FND_API.G_FALSE,
892                 p_validation_level  =>FND_API.G_VALID_LEVEL_FULL,
893                x_return_status                => l_return_status,
894                x_msg_count                    => l_msg_count,
895                x_msg_data                     => l_msg_data,
896                p_cash_receipt_id              => app_tab(i).cash_receipt_id,
897                p_amount_applied               => l_pay_refund_amount,
898                p_applied_payment_schedule_id  => -8,
899                p_receivables_trx_id           =>  g_nccr_receivables_trx_id,
900                p_apply_gl_date                => app_tab(i).reversal_gl_date,
901                p_comments                     => l_app_comments,
902                p_application_ref_type         => l_application_ref_type,
903                p_application_ref_id           => l_application_ref_id,
904                p_application_ref_num          => l_application_ref_num,
905                p_secondary_application_ref_id =>  app_tab(i).applied_customer_trx_id,
906                p_secondary_app_ref_type       => 'TRANSACTION',
907                p_secondary_app_ref_num        =>  app_info(i).trx_number,
908                p_receivable_application_id    => l_receivable_application_id
909 --              p_party_id => 1004
910               );
911            IF l_return_status  <> FND_API.G_RET_STS_SUCCESS THEN
912 
913                IF (l_msg_count = 1) THEN
914                   arp_standard.debug('ActivityApp: ' || l_MSG_DATA);
915                ELSIF(l_MSG_COUNT>1)THEN
916                   LOOP
917                      l_MSG_DATA:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_FALSE);
918                      IF (l_MSG_DATA IS NULL)THEN
919                         EXIT;
920                      END IF;
921                      arp_standard.debug('ActivityApp: ' || l_MSG_DATA);
922                   END LOOP;
923                END IF;
924 
925                arp_standard.debug('ActivityApp failed');
926 
927                RAISE l_activity_app_failed;
928             END IF; -- Handle API errors
929             --
930     END IF; -- Process PAyment Refund
931 
932 
933 
934 
935          <<end_loop>>
936          NULL;
937       END LOOP;
938    END LOOP;
939    --
940    <<after_loop>>
941    --
942    IF PG_DEBUG in ('Y', 'C') THEN
943       arp_standard.debug('arp_process_RETURNS.process_application_list()- ');
944    END IF;
945 EXCEPTION
946    WHEN OTHERS THEN
947       arp_standard.debug('EXCEPTION : arp_process_returns.process_application_list : ' || SQLERRM(SQLCODE));
948       RAISE;
949 END process_application_list;
950 
951 /*========================================================================
952  | Procedure unapply_receipts()
953  |
954  | DESCRIPTION
955  |      Unapply all receipt applications for the given invoice
956  |      and create the application list. This list will be used to create
957  |      special applications and apply remaining amount back to original
958  |      invoice
959  |
960  | PSEUDO CODE/LOGIC
961  |
962  | PARAMETERS
963  |
964  |   p_inv_customer_trx_id  - Invoice customer Trx ID
965  |   p_receipt_handling_option IN VARCHAR2
966  |
967  | RETURNS
968  |      nothing
969  |
970  | KNOWN ISSUES
971  |
972  |
973  |
974  | NOTES
975  |
976  |
977  |
978  | MODIFICATION HISTORY
979  | Date                  Author           Description of Changes
980  | 17-Jul-2003           Ramakant Alat    Created
981  |
982  *=======================================================================*/
983 
984 PROCEDURE unapply_receipts (p_inv_customer_trx_id IN NUMBER,
985                             p_receipt_handling_option IN VARCHAR2
986                            ) AS
987 
988 --
989 -- Cursor to get information about all receipt applications for the
990 -- given invoice.
991 --
992 /*GGADHAMS Modified the cursor for automated Receipt Handling using
993 Payment Refund*/
994 CURSOR c02 (p_customer_trx_id NUMBER,
995             p_receipt_handling_option IN VARCHAR2) IS
996 SELECT
997       ra.receivable_application_id,
998       ra.cash_receipt_id,
999       cr.amount,
1000       cr.currency_code rec_currency_code,
1001       inv.invoice_currency_code,
1002       ra.applied_customer_trx_id,
1003       ra.applied_payment_schedule_id,
1004       inv.trx_number,
1005       rm.payment_channel_code payment_type,
1006 --      DECODE(p_receipt_handling_option, 'REFUND',
1007 --                                     DECODE(rm.payment_channel_code,
1008 --                                            'CREDIT_CARD', 'REFUND',
1009 --                                            'ON-ACCOUNT'),
1010 --                                     'ON-ACCOUNT') rec_proc_option,
1011      DECODE(p_receipt_handling_option, 'REFUND',
1012                                      DECODE(rm.payment_channel_code,
1013                                             'CREDIT_CARD', 'REFUND',
1014                                             'BANK_ACCT_XFER','PAY_REFUND',
1015                                               null,'PAY_REFUND',
1016                                              'ON-ACCOUNT'),
1017                                      'ON-ACCOUNT') rec_proc_option,
1018       ra.amount_applied,
1019       ra.amount_applied_from
1020 FROM
1021       ar_receivable_applications ra
1022      ,ar_cash_receipts cr
1023      ,ar_receipt_methods rm
1024      ,ra_customer_trx inv
1025 WHERE
1026       ra.applied_customer_trx_id = p_customer_trx_id
1027   AND ra.cash_receipt_id         = cr.cash_receipt_id
1028   AND rm.receipt_method_id       = cr.receipt_method_id
1029   AND ra.display                 = 'Y'
1030   AND ra.applied_customer_trx_id = inv.customer_trx_id
1031 ORDER BY
1032    ra.APPLY_DATE,  --- This is for aging
1033    TO_NUMBER(DECODE(p_receipt_handling_option, 'REFUND',
1034                                      DECODE(rm.payment_channel_code, 'CREDIT_CARD',
1035                                                               2, 1) ,
1036                                      ra.amount_applied)) desc,
1037    ra.amount_applied desc;
1038 
1039 -- Local Variables
1040 l_application_ref_type      ar_receivable_applications.application_ref_type%type;
1041 l_application_ref_id        ar_receivable_applications.application_ref_id%type;
1042 l_secondary_application_ref_id  ar_receivable_applications.secondary_application_ref_id%type;
1043 l_application_ref_num       ar_receivable_applications.application_ref_num%type;
1044 l_receivable_application_id ar_receivable_applications.receivable_application_id%type;
1045 l_receivables_trx_id        ar_receivable_applications.receivables_trx_id%type;
1046 l_app_comments              ar_receivable_applications.comments%type;
1047 
1048 l_return_status             VARCHAR2(1) := FND_API.G_RET_STS_SUCCESS;
1049 l_msg_count                 NUMBER;
1050 l_msg_data                  VARCHAR2(2000);
1051 l_rid_reason                VARCHAR2(2000);
1052 l_unapp_amt_remaining       ar_receivable_applications.amount_applied%type;
1053 l_unapp_amount              ar_receivable_applications.amount_applied%type;
1054 l_ra_rec                    ar_receivable_applications%rowtype;
1055 l_unapply_failed            EXCEPTION;
1056 l_apply_failed              EXCEPTION;
1057 l_activity_app_failed       EXCEPTION;
1058 l_on_account_app_failed     EXCEPTION;
1059 l_ra_info                   app_info_type;
1060 l_rec_in_doubt              VARCHAR2(1):='N';
1061 BEGIN
1062    IF PG_DEBUG in ('Y', 'C') THEN
1063       arp_standard.debug('arp_process_RETURNS.unapply_receipts()+ ');
1064       arp_standard.debug('p_inv_customer_trx_id :<' || p_inv_customer_trx_id ||'>');
1065       arp_standard.debug('rec_hand_option :<' || p_receipt_handling_option ||'>');
1066    END IF;
1067    --
1068    --
1069    --
1070    FOR c02_rec IN c02(p_inv_customer_trx_id,
1071        p_receipt_handling_option) LOOP
1072       --
1073       --
1074       l_rec_in_doubt := 'N';
1075       l_rid_reason   := null;
1076       --
1077       -- If receipt is not already in doubt then check for doubt
1078       --
1079 
1080 -- Need to add check receipt in doubt for PAY_REFUND
1081       IF c02_rec.rec_proc_option = 'REFUND' THEN
1082          --
1083          IF PG_DEBUG in ('Y', 'C') THEN
1084             arp_standard.debug('CC receipt with refund request ');
1085          END IF;
1086          --
1087          IF inv_info(p_inv_customer_trx_id).all_recs_in_doubt THEN
1088             --
1089             l_rec_in_doubt := 'Y';
1090             l_rid_reason   := inv_info(p_inv_customer_trx_id).rid_reason;
1091             --
1092             IF PG_DEBUG in ('Y', 'C') THEN
1093                arp_standard.debug('All recs in doubt :<' || l_rid_reason ||'>');
1094             END IF;
1095             --
1096          ELSE
1097             --
1098             check_rec_in_doubt(p_cash_receipt_id=>c02_rec.cash_receipt_id,
1099                                 x_rec_in_doubt =>l_rec_in_doubt,
1100                                 x_rid_reason=>l_rid_reason,
1101                                 x_rec_proc_option => c02_rec.rec_proc_option);
1102             --
1103             --
1104             IF PG_DEBUG in ('Y', 'C') THEN
1105                arp_standard.debug('After RID chk :<' || l_rid_reason ||'>');
1106             END IF;
1107             --
1108          END IF;
1109          --
1110 
1111       END IF;
1112 
1113 
1114       IF c02_rec.rec_proc_option = 'PAY_REFUND' THEN
1115          --
1116          IF PG_DEBUG in ('Y', 'C') THEN
1117             arp_standard.debug('Non CC receipt with refund request ');
1118          END IF;
1119          --
1120          IF inv_info(p_inv_customer_trx_id).all_recs_in_doubt THEN
1121             --
1122             l_rec_in_doubt := 'Y';
1123             l_rid_reason   := inv_info(p_inv_customer_trx_id).rid_reason;
1124             --
1125             IF PG_DEBUG in ('Y', 'C') THEN
1126                arp_standard.debug('All recs in doubt :<' || l_rid_reason ||'>');
1127             END IF;
1128             --
1129          ELSE
1130             --
1131             check_rec_in_doubt(p_cash_receipt_id=>c02_rec.cash_receipt_id,
1132                                 x_rec_in_doubt =>l_rec_in_doubt,
1133                                 x_rid_reason=>l_rid_reason,
1134                                 x_rec_proc_option=> c02_rec.rec_proc_option);
1135             --
1136             --
1137             IF PG_DEBUG in ('Y', 'C') THEN
1138                arp_standard.debug('After Non CC  RID chk :<' || l_rid_reason ||'>');
1139             END IF;
1140             --
1141          END IF;
1142          --
1143 
1144       END IF;
1145 
1146 
1147       --
1148       -- Before we unapply receipt, get current application info.
1149       -- This application info will be used to create special apps and
1150       -- remaining amount re-app to old transaction.
1151       --
1152       -- Fetch Rec App record for the application
1153       --
1154       arp_app_pkg.fetch_p(p_ra_id=>c02_rec.receivable_application_id,
1155                           p_ra_rec=>l_ra_rec);
1156       --
1157       -- Add Receivable Application record to the list
1158       --
1159       -- This list will be used to create special apps e.g. REFUND, ON-ACCOUNT
1160       -- and re-app to old transaction
1161       --
1162       /* Bug 8686218 */
1163      IF PG_DEBUG in ('Y', 'C') THEN
1164        arp_standard.debug('Call to fetch_gl_date :  '||to_char(l_ra_rec.reversal_gl_date));
1165      END IF;
1166 
1167       fetch_gl_date(p_ra_rec => l_ra_rec,
1168                     p_gl_date => l_ra_rec.reversal_gl_date);
1169 
1170      IF PG_DEBUG in ('Y', 'C') THEN
1171        arp_standard.debug('Defaulted gl date via fetch_gl_date :  '||to_char(l_ra_rec.reversal_gl_date));
1172      END IF;
1173 
1174       l_ra_info.rec_proc_option   := c02_rec.rec_proc_option;
1175       l_ra_info.rec_in_doubt      := l_rec_in_doubt;
1176       l_ra_info.rid_reason        := l_rid_reason;
1177       l_ra_info.trx_number        := c02_rec.trx_number;
1178       l_ra_info.rec_currency_code := c02_rec.rec_currency_code;
1179       l_ra_info.inv_currency_code := c02_rec.invoice_currency_code;
1180       l_ra_info.customer_trx_id   := c02_rec.applied_customer_trx_id;  /* bug 9909157 */
1181       --
1182       IF c02_rec.rec_currency_code <> c02_rec.invoice_currency_code THEN
1183          l_ra_info.cross_currency := TRUE;
1184       ELSE
1185          l_ra_info.cross_currency := FALSE;
1186       END IF;
1187       --
1188       l_ra_info.inv_currency_code := c02_rec.invoice_currency_code;
1189       --
1190       add_ra_to_list(p_ra_info=>l_ra_info, p_ra_rec=>l_ra_rec);
1191       --
1192       IF PG_DEBUG in ('Y', 'C') THEN
1193          arp_standard.debug('rec_app_id :<' ||
1194             c02_rec.receivable_application_id ||'>');
1195          arp_standard.debug('rec_in_doubt :<' || l_rec_in_doubt ||'>');
1196          arp_standard.debug('rec_in_doubt_reason :<' ||
1197             l_rid_reason ||'>');
1198          arp_standard.debug('rec_proc_option :<' ||
1199             c02_rec.rec_proc_option ||'>');
1200       END IF;
1201       --
1202       -- Unapply the application
1203       --
1204       ar_receipt_api_pub.Unapply(
1205                p_api_version               => 1.0,
1206                x_return_status             => l_return_status,
1207                x_msg_count                 => l_msg_count,
1208                x_msg_data                  => l_msg_data,
1209                p_receivable_application_id => c02_rec.receivable_application_id,
1210                p_reversal_gl_date          => l_ra_rec.reversal_gl_date
1211               );
1212 
1213       IF l_return_status  <> FND_API.G_RET_STS_SUCCESS THEN
1214 
1215          IF (l_msg_count = 1) THEN
1216             arp_standard.debug('Unapply: ' || l_MSG_DATA);
1217          ELSIF(l_MSG_COUNT>1)THEN
1218             LOOP
1219                l_MSG_DATA:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_FALSE);
1220                IF (l_MSG_DATA IS NULL)THEN
1221                   EXIT;
1222                END IF;
1223                arp_standard.debug('UNapply: ' || l_MSG_DATA);
1224             END LOOP;
1225          END IF;
1226 
1227          arp_standard.debug('Unapplication failed');
1228          RAISE l_unapply_failed;
1229       END IF;
1230 
1231    END LOOP;
1232 
1233    IF PG_DEBUG in ('Y', 'C') THEN
1234       arp_standard.debug('arp_process_RETURNS.unapply_receipts()- ');
1235    END IF;
1236 EXCEPTION
1237    WHEN OTHERS THEN
1238       arp_standard.debug('arp_process_returns.unapply_receipts : '
1239          || SQLERRM(SQLCODE));
1240       RAISE;
1241 
1242 END unapply_receipts;
1243 
1244 --
1245 -- Add invoice to the list, which will be used for further processing
1246 --
1247 
1248 PROCEDURE add_invoice (p_customer_trx_id IN NUMBER) IS
1249 BEGIN
1250    IF PG_DEBUG in ('Y', 'C') THEN
1251       arp_standard.debug('arp_process_RETURNS.add_invoice()+ ');
1252       arp_standard.debug('p_customer_trx_id :<' || p_customer_trx_id ||'>');
1253    END IF;
1254 
1255    IF inv_info.EXISTS(p_customer_trx_id) THEN
1256       inv_info(p_customer_trx_id).num_of_cms :=
1257          inv_info(p_customer_trx_id).num_of_cms + 1;
1258    ELSE
1259       inv_info(p_customer_trx_id).num_of_cms := 1;
1260    END IF;
1261 
1262    IF PG_DEBUG in ('Y', 'C') THEN
1263       arp_standard.debug('arp_process_RETURNS.add_invoice()- ');
1264    END IF;
1265 EXCEPTION
1266    WHEN OTHERS THEN
1267       arp_standard.debug('arp_process_returns.add_invoice : ' ||
1268       SQLERRM(SQLCODE));
1269       RAISE;
1270 END;
1271 
1272 --
1273 -- Add Receipt Application to the list,
1274 -- which will be used for further processing
1275 --
1276 
1277 PROCEDURE add_ra_to_list(p_ra_info  IN app_info_type,
1278                          p_ra_rec   IN ar_receivable_applications%rowtype) AS
1279 l_cnt  NUMBER := app_info.COUNT;
1280 BEGIN
1281    --
1282    IF PG_DEBUG in ('Y', 'C') THEN
1283       arp_standard.debug('arp_process_RETURNS.add_ra_to_list()+ ');
1284       arp_standard.debug('count :<' || l_cnt ||'>');
1285    END IF;
1286    --
1287    l_cnt := l_cnt + 1;
1288    app_info(l_cnt) := p_ra_info;
1289    app_tab(l_cnt)  := p_ra_rec;
1290    --
1291    IF PG_DEBUG in ('Y', 'C') THEN
1292       arp_standard.debug('arp_process_RETURNS.add_ra_to_list()- ');
1293    END IF;
1294    --
1295 EXCEPTION
1296    WHEN OTHERS THEN
1297       arp_standard.debug('arp_process_returns.add_ra_to_list : ' ||
1298       SQLERRM(SQLCODE));
1299       RAISE;
1300 END;
1301 --
1302 -- Get Total CM amount for a given invoice
1303 --
1304 FUNCTION get_total_cm_amount (p_inv_customer_trx_id IN NUMBER,
1305                               p_request_id IN NUMBER) RETURN NUMBER AS
1306 
1307 l_total_cm_amount  RA_CUSTOMER_TRX_LINES.EXTENDED_AMOUNT%TYPE;
1308 
1309 BEGIN
1310    --
1311    IF PG_DEBUG in ('Y', 'C') THEN
1312       arp_standard.debug('arp_process_RETURNS.get_total_cm_amount()+ ');
1313       arp_standard.debug('p_inv_customer_trx_id :<'
1314          || p_inv_customer_trx_id ||'>');
1315    END IF;
1316    --
1317    SELECT NVL(SUM(extended_amount) , 0)
1318    INTO   l_total_cm_amount
1319    FROM   RA_CUSTOMER_TRX_LINES
1320    WHERE  previous_customer_trx_id = p_inv_customer_trx_id
1321    AND    request_id               = p_request_id;
1322    --
1323    IF PG_DEBUG in ('Y', 'C') THEN
1324       arp_standard.debug('l_total_cm_amount :<'
1325          || l_total_cm_amount ||'>');
1326       arp_standard.debug('arp_process_RETURNS.get_total_cm_amount()- ');
1327    END IF;
1328    --
1329 
1330    RETURN l_total_cm_amount;
1331 EXCEPTION
1332    WHEN OTHERS THEN
1333       arp_standard.debug('EXCEPTION:arp_process_returns.get_total_cm_amount : '
1334       || SQLERRM(SQLCODE));
1335       RAISE;
1336 
1337 END get_total_cm_amount;
1338 
1339 --
1340 -- Get total payment types for all receipts applied to this invoice
1341 --
1342 --Modified the select using Payment Channel code to identify the payment type
1343 --Need confirmation on count and NVL
1344 FUNCTION get_total_payment_types (p_inv_customer_trx_id IN NUMBER)
1345 RETURN NUMBER AS
1346 
1347 l_total_payment_types     NUMBER:=0;
1348 l_total_cc_pmts           NUMBER:=0;
1349 
1350 BEGIN
1351    --
1352    IF PG_DEBUG in ('Y', 'C') THEN
1353       arp_standard.debug('arp_process_RETURNS.get_total_payment_types()+ ');
1354       arp_standard.debug('p_inv_customer_trx_id :<'
1355          || p_inv_customer_trx_id ||'>');
1356    END IF;
1357    --
1358    SELECT
1359 --          count(distinct NVL(rm.payment_channel_code, 'CHECK')) ,
1360             count(distinct NVL(rm.payment_channel_code, 'CHECK')) ,
1361 --          sum(DECODE(rm.payment_channel_code, 'CREDIT_CARD', 1, 0))
1362             sum(DECODE(rm.payment_channel_code, 'CREDIT_CARD', 1, 0))
1363    INTO
1364           l_total_payment_types,
1365           l_total_cc_pmts
1366    FROM   AR_RECEIVABLE_APPLICATIONS ra,
1367           ar_cash_receipts cr,
1368           ar_receipt_methods rm
1369    WHERE  ra.applied_customer_trx_id = p_inv_customer_trx_id
1370      AND  ra.cash_receipt_id         = cr.cash_receipt_id
1371      AND  cr.receipt_method_id       = rm.receipt_method_id;
1372 
1373    IF l_total_cc_pmts = 0 THEN
1374       l_total_payment_types := 0;
1375    END IF;
1376    --
1377    IF PG_DEBUG in ('Y', 'C') THEN
1378       arp_standard.debug('l_total_payment_types :<'
1379          || l_total_payment_types ||'>');
1380       arp_standard.debug('arp_process_RETURNS.get_total_payment_types()- ');
1381    END IF;
1382    --
1383    RETURN l_total_payment_types;
1384    --
1385 EXCEPTION
1386    WHEN OTHERS THEN
1387       arp_standard.debug('EXCEPTION:arp_process_returns.get_total_payment_types : '
1388       || SQLERRM(SQLCODE));
1389       RAISE;
1390 
1391 END get_total_payment_types;
1392 
1393 
1394 --
1395 -- Get receipt and refund amounts
1396 --
1397 PROCEDURE get_receipt_amounts (p_cash_receipt_id IN NUMBER,
1398                             x_receipt_amount OUT NOCOPY NUMBER,
1399                             x_refund_amount  OUT NOCOPY NUMBER,
1400 		            x_rec_proc_option IN VARCHAR2) AS
1401 
1402 BEGIN
1403    --
1404    IF PG_DEBUG in ('Y', 'C') THEN
1405       arp_standard.debug('arp_process_RETURNS.get_receipt_amounts()+ ');
1406       arp_standard.debug('p_cash_receipt_id :<'
1407          || p_cash_receipt_id ||'>');
1408    END IF;
1409    --
1410    x_receipt_amount := 0;
1411    x_refund_amount := 0;
1412 
1413 IF  x_rec_proc_option = 'REFUND' THEN
1414 
1415    SELECT NVL(amount, 0), NVL(SUM(amount_applied) , 0)
1416    INTO   x_receipt_amount, x_refund_amount
1417    FROM   ar_cash_receipts cr,  ar_receivable_applications ra
1418    WHERE  cr.cash_receipt_id = p_cash_receipt_id
1419    AND    cr.cash_receipt_id = ra.cash_receipt_id(+)
1420    AND    ra.applied_payment_schedule_id(+)  = -6
1421    AND    ra.display(+)  = 'Y'
1422    GROUP BY  amount;
1423 
1424 ELSIF  x_rec_proc_option = 'PAY_REFUND' THEN
1425    SELECT NVL(amount, 0), NVL(SUM(amount_applied) , 0)
1426    INTO   x_receipt_amount, x_refund_amount
1427    FROM   ar_cash_receipts cr,  ar_receivable_applications ra
1428    WHERE  cr.cash_receipt_id = p_cash_receipt_id
1429    AND    cr.cash_receipt_id = ra.cash_receipt_id(+)
1430    AND    ra.applied_payment_schedule_id(+)  = -8
1431    AND    ra.display(+)  = 'Y'
1432    GROUP BY  amount;
1433 
1434 END IF;
1435 
1436    --
1437    IF PG_DEBUG in ('Y', 'C') THEN
1438       arp_standard.debug('x_receipt_amount :<'
1439          || x_receipt_amount ||'>');
1440       arp_standard.debug('x_refund_amount :<'
1441          || x_refund_amount ||'>');
1442       arp_standard.debug('arp_process_RETURNS.get_receipt_amounts()- ');
1443    END IF;
1444    --
1445 
1446 EXCEPTION
1447    WHEN NO_DATA_FOUND THEN
1448       NULL;
1449    WHEN OTHERS THEN
1450       arp_standard.debug('EXCEPTION:arp_process_returns.get_receipt_amounts : '
1451       || SQLERRM(SQLCODE));
1452       RAISE;
1453 END;
1454 
1455 /*===========================================================================+
1456  | PORCEDURE                                                                 |
1457  |    check_rec_in_doubt                                                     |
1458  |                                                                           |
1459  | DESCRIPTION                                                               |
1460  |    This function checks if given receipt is doubt                         |
1461  |    Given receipt can be in doubt for any of the following reasons         |
1462  |    . If receipt is a CC receipt and is not remitted                       |
1463  |    . If receipt has Special application of Claims Investigation           |
1464  |    . If the receipt is Debit Memo reversed                                |
1465  |    . If the Receipt is a Non CC receipt and is not cleared
1466  |                                                                           |
1467  | SCOPE - PUBLIC                                                            |
1468  |                                                                           |
1469  | ARGUMENTS  : IN  : p_cash_receipt_id                                      |
1470  |                                                                           |
1471  |            : OUT : x_rec_in_doubt (Y/N)                                   |
1472  |              OUT : x_rid_reason                                           |
1473  |                                                                           |
1474  | NOTES      :                                                              |
1475  |                                                                           |
1476  |                                                                           |
1477  | MODIFICATION HISTORY                                                      |
1478  |     19-Jun-03    Ramakant Alat   Created                                  |
1479  |     27-Dec-05    Gyanajyothi G   Added the check for Non CC receipt       |
1480  +===========================================================================*/
1481 PROCEDURE check_rec_in_doubt(p_cash_receipt_id IN NUMBER,
1482                              x_rec_in_doubt OUT NOCOPY VARCHAR2,
1483                              x_rid_reason OUT NOCOPY VARCHAR2,
1484 		   	     x_rec_proc_option IN VARCHAR2) IS
1485 BEGIN
1486    ---
1487    IF PG_DEBUG in ('Y', 'C') THEN
1488       arp_standard.debug('arp_process_RETURNS.check_rec_in_doubt()+ ');
1489    END IF;
1490    ---
1491    x_rec_in_doubt := 'N';
1492    x_rid_reason   := null;
1493    ---
1494    --- For CC receipts, receipt should be remitted
1495    ---
1496   IF  x_rec_proc_option = 'REFUND' THEN
1497    BEGIN
1498       SELECT 'Y', arp_standard.fnd_message('AR_RID_NOT_REMITTED_OR_CLEARED')
1499       INTO   x_rec_in_doubt, x_rid_reason
1500       FROM   dual
1501       WHERE
1502          (
1503            NOT EXISTS
1504            (
1505              SELECT 1
1506              FROM  AR_CASH_RECEIPT_HISTORY crh
1507              WHERE crh.cash_receipt_id = p_cash_receipt_id
1508              AND   crh.status IN ('REMITTED', 'CLEARED')
1509            )
1510          );
1511    EXCEPTION
1512       WHEN NO_DATA_FOUND THEN
1513          NULL;
1514       WHEN OTHERS THEN
1515          arp_standard.debug('Unexpected error '||sqlerrm||
1516             ' occurred in arp_process_returns.check_rec_in_doubt');
1517          RAISE;
1518    END;
1519 
1520    ---
1521    IF PG_DEBUG in ('Y', 'C') THEN
1522       arp_standard.debug('After REFUND x_rec_in_doubt[x_rid_reason]: ' || x_rec_in_doubt ||
1523       '[' || x_rid_reason || ']');
1524    END IF;
1525 
1526   ELSIF  x_rec_proc_option = 'PAY_REFUND' THEN
1527    ---
1528    --- For Non CC Receipts , receipt should be cleared
1529    ---
1530     BEGIN
1531       SELECT 'Y', arp_standard.fnd_message('AR_RID_NOT_CLEARED')
1532       INTO   x_rec_in_doubt, x_rid_reason
1533       FROM   dual
1534       WHERE
1535          (
1536            NOT EXISTS
1537            (
1538              SELECT 1
1539              FROM  AR_CASH_RECEIPT_HISTORY crh
1540              WHERE crh.cash_receipt_id = p_cash_receipt_id
1541              AND   crh.status IN ('CLEARED')
1542            )
1543          );
1544    EXCEPTION
1545       WHEN NO_DATA_FOUND THEN
1546          NULL;
1547       WHEN OTHERS THEN
1548          arp_standard.debug('Unexpected error '||sqlerrm||
1549             ' occurred in arp_process_returns.check_rec_in_doubt');
1550          RAISE;
1551    END;
1552 
1553    ---
1554    IF PG_DEBUG in ('Y', 'C') THEN
1555       arp_standard.debug('After Non CC REFUND x_rec_in_doubt[x_rid_reason]: ' || x_rec_in_doubt ||
1556       '[' || x_rid_reason || ']');
1557    END IF;
1558   END IF;
1559 
1560 
1561    ---
1562    ---
1563    --- There should not be any Claims Investigation or CB special application
1564    ---
1565    BEGIN
1566       SELECT 'Y', arp_standard.fnd_message('AR_RID_CLAIM_OR_CB_APP_EXISTS')
1567       INTO   x_rec_in_doubt, x_rid_reason
1568       FROM   dual
1569       WHERE
1570            EXISTS
1571            (
1572              SELECT 1
1573              FROM   ar_receivable_applications ra
1574              WHERE  ra.cash_receipt_id = p_cash_receipt_id
1575              AND    applied_payment_schedule_id IN (-4,  -5)
1576              AND    display = 'Y'
1577            );
1578    EXCEPTION
1579       WHEN NO_DATA_FOUND THEN
1580          NULL;
1581       WHEN OTHERS THEN
1582          arp_standard.debug('Unexpected error '||sqlerrm||
1583             ' occurred in arp_process_returns.check_rec_in_doubt');
1584          RAISE;
1585    END;
1586 
1587    ---
1588    IF PG_DEBUG in ('Y', 'C') THEN
1589       arp_standard.debug('After CLAIMS x_rec_in_doubt[x_rid_reason]: ' ||
1590          x_rec_in_doubt || '[' || x_rid_reason || ']');
1591    END IF;
1592    ---
1593    ---
1594    --- Receipt should not be reversed
1595    ---
1596    BEGIN
1597       SELECT 'Y', arp_standard.fnd_message('AR_RID_RECEIPT_REVERSED')
1598       INTO   x_rec_in_doubt, x_rid_reason
1599       FROM   dual
1600       WHERE
1601            EXISTS
1602            (
1603              SELECT 1
1604              FROM   ar_cash_receipts cr1
1605              WHERE  cr1.cash_receipt_id = p_cash_receipt_id
1606              AND    cr1.reversal_date is not null
1607            );
1608    EXCEPTION
1609       WHEN NO_DATA_FOUND THEN
1610          NULL;
1611       WHEN OTHERS THEN
1612          arp_standard.debug('Unexpected error '||sqlerrm||
1613             ' occurred in arp_process_returns.check_rec_in_doubt');
1614          RAISE;
1615    END;
1616 
1617    ---
1618    IF PG_DEBUG in ('Y', 'C') THEN
1619       arp_standard.debug('After DM reverse x_rec_in_doubt[x_rid_reason]: ' ||
1620       x_rec_in_doubt || '[' || x_rid_reason || ']');
1621    END IF;
1622    ---
1623 <<end_of_proc>>
1624    ---
1625    IF PG_DEBUG in ('Y', 'C') THEN
1626       arp_standard.debug('arp_process_RETURNS.check_rec_in_doubt()- ');
1627    END IF;
1628    ---
1629 EXCEPTION
1630    WHEN OTHERS THEN
1631       arp_standard.debug('Unexpected error '||sqlerrm||
1632          ' occurred in arp_process_returns.check_rec_in_doubt');
1633       RAISE;
1634 END check_rec_in_doubt;
1635 
1636 /*===========================================================================+
1637  | FUNCTION                                                                  |
1638  |    get_on_acct_cm_apps                                                    |
1639  |                                                                           |
1640  | DESCRIPTION                                                               |
1641  |    This function returns the total number of on-acct cm applications      |
1642  |    to the given transaction                                               |
1643  |                                                                           |
1644  | SCOPE - PUBLIC                                                            |
1645  |                                                                           |
1646  | ARGUMENTS  : IN:   p_customer_trx_id                                      |
1647  |                                                                           |
1648  | RETURNS    : Total number of on-account credit memo applications          |
1649  |                                                                           |
1650  | NOTES      :                                                              |
1651  |                                                                           |
1652  |                                                                           |
1653  | MODIFICATION HISTORY                                                      |
1654  |     19-Jun-03    Ramakant Alat   Created                                  |
1655  +===========================================================================*/
1656 
1657 FUNCTION get_on_acct_cm_apps(p_customer_trx_id   IN NUMBER)
1658 RETURN NUMBER  IS
1659 l_count NUMBER;
1660 BEGIN
1661    ---
1662    IF PG_DEBUG in ('Y', 'C') THEN
1663       arp_standard.debug('arp_process_RETURNS.get_on_acct_cm_apps()+ ');
1664       arp_standard.debug('p_customer_trx_id :<'
1665          || p_customer_trx_id ||'>');
1666    END IF;
1667    ---
1668    select count(*)
1669      into l_count
1670    from   ar_receivable_applications app,
1671           ra_customer_trx oncm
1672    where app.applied_customer_trx_id = p_customer_trx_id
1673      and app.status = 'APP'
1674      and app.application_type = 'CM'
1675      and app.display = 'Y'
1676      and app.customer_trx_id = oncm.customer_trx_id
1677      and oncm.previous_customer_trx_id IS NULL;
1678    ---
1679    IF PG_DEBUG in ('Y', 'C') THEN
1680       arp_standard.debug('arp_process_RETURNS.get_on_acct_cm_apps()- ');
1681    END IF;
1682    ---
1683    RETURN l_count;
1684 
1685 EXCEPTION
1686    WHEN OTHERS THEN
1687    arp_standard.debug('Unexpected error '||sqlerrm||
1688                       ' occurred in arp_process_returns.get_on_acct_cm_apps');
1689    RAISE;
1690 END get_on_acct_cm_apps;
1691 
1692 /*===========================================================================+
1693  | FUNCTION                                                                  |
1694  |    get_neg_inv_apps                                                       |
1695  |                                                                           |
1696  | DESCRIPTION                                                               |
1697  |    This function returns the total number of negative inv applications    |
1698  |    across different receipts                                              |
1699  |                                                                           |
1700  | SCOPE - PUBLIC                                                            |
1701  |                                                                           |
1702  | ARGUMENTS  : IN:   p_customer_trx_id                                      |
1703  |                                                                           |
1704  | RETURNS    : Total number of negative inv applications                    |
1705  |                                                                           |
1706  | NOTES      :                                                              |
1707  |                                                                           |
1708  |                                                                           |
1709  | MODIFICATION HISTORY                                                      |
1710  |     29-Oct-03    Ramakant Alat   Created                                  |
1711  +===========================================================================*/
1712 
1713 FUNCTION get_neg_inv_apps(p_customer_trx_id   IN NUMBER)
1714 RETURN NUMBER  IS
1715 l_count NUMBER;
1716 BEGIN
1717    ---
1718    IF PG_DEBUG in ('Y', 'C') THEN
1719       arp_standard.debug('arp_process_RETURNS.get_neg_inv_apps()+ ');
1720       arp_standard.debug('p_customer_trx_id :<'
1721          || p_customer_trx_id ||'>');
1722    END IF;
1723    ---
1724    select count(*)
1725      into l_count
1726    from   ar_receivable_applications app
1727    where app.applied_customer_trx_id = p_customer_trx_id
1728      and app.status = 'APP'
1729      and app.application_type = 'CASH'
1730      and app.display = 'Y'
1731      and app.amount_applied < 0;
1732    ---
1733    IF PG_DEBUG in ('Y', 'C') THEN
1734       arp_standard.debug('arp_process_RETURNS.get_neg_inv_apps()- ');
1735    END IF;
1736    ---
1737    RETURN l_count;
1738 
1739 EXCEPTION
1740    WHEN OTHERS THEN
1741    arp_standard.debug('Unexpected error '||sqlerrm||
1742                       ' occurred in arp_process_returns.get_neg_inv_apps');
1743    RAISE;
1744 END get_neg_inv_apps;
1745 
1746 
1747 /*===========================================================================+
1748  | FUNCTION                                                                  |
1749  |    get_llca_apps                                                          |
1750  |                                                                           |
1751  | DESCRIPTION                                                               |
1752  |    This function checks if there exists a Line Level Cash Applications    |
1753  |    to the given transaction                                               |
1754  |                                                                           |
1755  | SCOPE - PUBLIC                                                            |
1756  |                                                                           |
1757  | ARGUMENTS  : IN:   p_customer_trx_id                                      |
1758  |                                                                           |
1759  | RETURNS    : Total of  LLCA                                               |
1760  |                                                                           |
1761  | NOTES      :                                                              |
1762  |                                                                           |
1763  |                                                                           |
1764  | MODIFICATION HISTORY                                                      |
1765  |     29-Dec-05   Gyanajyothi G    Created                                  |
1766  +===========================================================================*/
1767 FUNCTION get_llca_apps(p_customer_trx_id   IN NUMBER)
1768 RETURN NUMBER  IS
1769 l_count NUMBER;
1770 BEGIN
1771    ---
1772    IF PG_DEBUG in ('Y', 'C') THEN
1773       arp_standard.debug('arp_process_RETURNS.get_llca_apps()+ ');
1774       arp_standard.debug('p_customer_trx_id :<'
1775          || p_customer_trx_id ||'>');
1776    END IF;
1777    ---
1778    select count(*)
1779      into l_count
1780    from   ar_activity_details  aad,
1781           ra_customer_trx_lines lines
1782    where
1783      lines.customer_trx_id =  p_customer_trx_id
1784      and   nvl(aad.CURRENT_ACTIVITY_FLAG,'Y') = 'Y'
1785      and aad.customer_trx_line_id = lines.customer_trx_line_id;
1786 
1787    ---
1788    IF PG_DEBUG in ('Y', 'C') THEN
1789       arp_standard.debug('arp_process_RETURNS.get_llca_apps()- ');
1790    END IF;
1791    ---
1792    RETURN l_count;
1793 
1794 EXCEPTION
1795    WHEN OTHERS THEN
1796    arp_standard.debug('Unexpected error '||sqlerrm||
1797                       ' occurred in arp_process_returns.get_llca_apps');
1798    RAISE;
1799 END get_llca_apps;
1800 
1801 
1802 
1803 /*===========================================================================+
1804  | PROCEDURE                                                                 |
1805  |    populate_dff_and_gdf                                                   |
1806  |                                                                           |
1807  | DESCRIPTION                                                               |
1808  |    This procedure populates the Global DFF and DFF from the old           |
1809  |    record                                                                 |
1810  |                                                                           |
1811  | SCOPE - PUBLIC                                                            |
1812  |                                                                           |
1813  | ARGUMENTS  : IN  :   p_ra_rec                                             |
1814  |              OUT :   x_dff_rec                                            |
1815  |                      x_gdf_rec                                            |
1816  |                                                                           |
1817  |                                                                           |
1818  | NOTES      :                                                              |
1819  |                                                                           |
1820  |                                                                           |
1821  | MODIFICATION HISTORY                                                      |
1822  |     27-Jul-03    Ramakant Alat   Created                                  |
1823  +===========================================================================*/
1824 
1825 PROCEDURE populate_dff_and_gdf(p_ra_rec  IN ar_receivable_applications%rowtype,
1826                                x_dff_rec OUT NOCOPY
1827                                   ar_receipt_api_pub.attribute_rec_type,
1828                                x_gdf_rec OUT NOCOPY
1829                                   ar_receipt_api_pub.global_attribute_rec_type)
1830 AS
1831 BEGIN
1832    ---
1833    IF PG_DEBUG in ('Y', 'C') THEN
1834       arp_standard.debug('arp_process_RETURNS.populate_dff_and_gdf()+ ');
1835    END IF;
1836    ---
1837    x_dff_rec.attribute_category:=p_ra_rec.attribute_category;
1838    x_dff_rec.attribute1        :=p_ra_rec.attribute1;
1839    x_dff_rec.attribute2        :=p_ra_rec.attribute2;
1840    x_dff_rec.attribute3        :=p_ra_rec.attribute3;
1841    x_dff_rec.attribute4        :=p_ra_rec.attribute4;
1842    x_dff_rec.attribute5        :=p_ra_rec.attribute5;
1843    x_dff_rec.attribute6        :=p_ra_rec.attribute6;
1844    x_dff_rec.attribute7        :=p_ra_rec.attribute7;
1845    x_dff_rec.attribute8        :=p_ra_rec.attribute8;
1846    x_dff_rec.attribute9        :=p_ra_rec.attribute9;
1847    x_dff_rec.attribute10       :=p_ra_rec.attribute10;
1848    x_dff_rec.attribute11       :=p_ra_rec.attribute11;
1849    x_dff_rec.attribute12       :=p_ra_rec.attribute12;
1850    x_dff_rec.attribute13       :=p_ra_rec.attribute13;
1851    x_dff_rec.attribute14       :=p_ra_rec.attribute14;
1852    x_dff_rec.attribute15       :=p_ra_rec.attribute15;
1853    ---
1854    ---
1855    x_gdf_rec.global_attribute_category :=p_ra_rec.global_attribute_category ;
1856    x_gdf_rec.global_attribute1         :=p_ra_rec.global_attribute1;
1857    x_gdf_rec.global_attribute2         :=p_ra_rec.global_attribute2;
1858    x_gdf_rec.global_attribute3         :=p_ra_rec.global_attribute3;
1859    x_gdf_rec.global_attribute4         :=p_ra_rec.global_attribute4;
1860    x_gdf_rec.global_attribute5         :=p_ra_rec.global_attribute5;
1861    x_gdf_rec.global_attribute6         :=p_ra_rec.global_attribute6;
1862    x_gdf_rec.global_attribute7         :=p_ra_rec.global_attribute7;
1863    x_gdf_rec.global_attribute8         :=p_ra_rec.global_attribute8;
1864    x_gdf_rec.global_attribute9         :=p_ra_rec.global_attribute9;
1865    x_gdf_rec.global_attribute10        :=p_ra_rec.global_attribute10;
1866    x_gdf_rec.global_attribute11        :=p_ra_rec.global_attribute11;
1867    x_gdf_rec.global_attribute12        :=p_ra_rec.global_attribute12;
1868    x_gdf_rec.global_attribute13        :=p_ra_rec.global_attribute13;
1869    x_gdf_rec.global_attribute14        :=p_ra_rec.global_attribute14;
1870    x_gdf_rec.global_attribute15        :=p_ra_rec.global_attribute15;
1871    x_gdf_rec.global_attribute16        :=p_ra_rec.global_attribute16;
1872    x_gdf_rec.global_attribute17        :=p_ra_rec.global_attribute17;
1873    x_gdf_rec.global_attribute18        :=p_ra_rec.global_attribute18;
1874    x_gdf_rec.global_attribute19        :=p_ra_rec.global_attribute19;
1875    x_gdf_rec.global_attribute20        :=p_ra_rec.global_attribute20;
1876    ---
1877    ---
1878    IF PG_DEBUG in ('Y', 'C') THEN
1879       arp_standard.debug('arp_process_RETURNS.populate_dff_and_gdf()- ');
1880    END IF;
1881    ---
1882 EXCEPTION
1883    WHEN OTHERS THEN
1884    arp_standard.debug('Unexpected error '||sqlerrm||
1885                       ' occurred in arp_process_returns.populate_dff_and_gdf');
1886    RAISE;
1887 END populate_dff_and_gdf;
1888 
1889 
1890 /*===========================================================================+
1891  | FUNCTION                                                                  |
1892  |    get_amount_applied                                                     |
1893  |                                                                           |
1894  | DESCRIPTION                                                               |
1895  |    This function returns the amount applied by receipts for a given       |
1896  |    invoice for requested bucket                                           |
1897  |                                                                           |
1898  | SCOPE - PUBLIC                                                            |
1899  |                                                                           |
1900  | ARGUMENTS  : IN:   p_customer_trx_id                                      |
1901  |              IN:   p_line_type                                            |
1902  |                                                                           |
1903  | RETURNS    : amount applied for the given bucket by receipts              |
1904  |                                                                           |
1905  | NOTES      :                                                              |
1906  |                                                                           |
1907  |                                                                           |
1908  | MODIFICATION HISTORY                                                      |
1909  |     26-Jul-03    Ramakant Alat   Created                                  |
1910  +===========================================================================*/
1911 
1912 FUNCTION get_amount_applied(p_customer_trx_id   IN NUMBER,
1913                             p_line_type IN VARCHAR2)
1914 RETURN NUMBER  IS
1915 
1916 l_total_amount   ar_receivable_applications.amount_applied%type:=0;
1917 l_amt_app_rec    amt_app_type;
1918 
1919 l_line_amount    ar_receivable_applications.amount_applied%type:=0;
1920 l_tax_amount     ar_receivable_applications.amount_applied%type:=0;
1921 l_frt_amount     ar_receivable_applications.amount_applied%type:=0;
1922 l_charges_amount ar_receivable_applications.amount_applied%type:=0;
1923 l_applied_amount ar_receivable_applications.amount_applied%type:=0;
1924 
1925 BEGIN
1926    ---
1927    IF PG_DEBUG in ('Y', 'C') THEN
1928       arp_standard.debug('arp_process_RETURNS.get_amount_applied()+ ');
1929       arp_standard.debug('Customer Trx Id : ' || p_customer_trx_id);
1930       arp_standard.debug('p_line_type : ' || p_line_type);
1931    END IF;
1932    --
1933    -- Adjust amount applied iff invoice is in the list created during validation
1934    --
1935    IF inv_info.EXISTS(p_customer_trx_id) THEN
1936       --
1937       IF amt_app_tab.EXISTS(p_customer_trx_id) THEN
1938          --
1939          IF PG_DEBUG in ('Y', 'C') THEN
1940             arp_standard.debug('Cache Hit...');
1941          END IF;
1942          --
1943          null;
1944          --
1945       ELSE
1946          --
1947          IF PG_DEBUG in ('Y', 'C') THEN
1948             arp_standard.debug('Database Hit...');
1949          END IF;
1950          --
1951          --
1952          --
1953          SELECT
1954             SUM(NVL(line_applied, 0) + NVL(line_ediscounted, 0)),
1955             SUM(NVL(tax_applied, 0) + NVL(tax_ediscounted, 0)),
1956             SUM(NVL(freight_applied, 0) + NVL(freight_ediscounted, 0)),
1957             SUM(NVL(receivables_charges_applied, 0)
1958              + NVL(charges_ediscounted, 0)),
1959             SUM(NVL(amount_applied, 0) + NVL(earned_discount_taken, 0))
1960          INTO
1961             l_line_amount,
1962             l_tax_amount,
1963             l_frt_amount,
1964             l_charges_amount,
1965             l_applied_amount
1966          FROM
1967             ar_receivable_applications
1968          WHERE
1969             applied_customer_trx_id = p_customer_trx_id
1970          AND application_type = 'CASH'   -- Consider only receipt applications
1971          AND display = 'Y';
1972          --
1973          --
1974          amt_app_tab(p_customer_trx_id).line_applied := NVL(l_line_amount, 0);
1975          amt_app_tab(p_customer_trx_id).tax_applied := NVL(l_tax_amount, 0);
1976          amt_app_tab(p_customer_trx_id).freight_applied := NVL(l_frt_amount, 0);
1977          amt_app_tab(p_customer_trx_id).charges_applied := NVL(l_charges_amount, 0);
1978          amt_app_tab(p_customer_trx_id).amount_applied := NVL(l_applied_amount, 0);
1979          --
1980          --
1981       END IF;
1982       --
1983       IF p_line_type = 'LINE' THEN
1984          l_total_amount := amt_app_tab(p_customer_trx_id).line_applied;
1985       ELSIF p_line_type = 'TAX' THEN
1986          l_total_amount := amt_app_tab(p_customer_trx_id).tax_applied;
1987       ELSIF p_line_type = 'FREIGHT' THEN
1988          l_total_amount := amt_app_tab(p_customer_trx_id).freight_applied;
1989       ELSIF p_line_type = 'CHARGES' THEN
1990          l_total_amount := amt_app_tab(p_customer_trx_id).charges_applied;
1991       ELSE
1992          l_total_amount := amt_app_tab(p_customer_trx_id).amount_applied;
1993       END IF;
1994       --
1995    ELSE
1996       l_total_amount := 0;
1997    END IF;
1998    ---
1999    IF PG_DEBUG in ('Y', 'C') THEN
2000       arp_standard.debug('Total Amount : ' || l_total_amount);
2001       arp_standard.debug('arp_process_RETURNS.get_amount_applied()- ');
2002    END IF;
2003    --
2007 EXCEPTION
2004 
2005    RETURN l_total_amount;
2006 
2008    WHEN OTHERS THEN
2009    arp_standard.debug('Unexpected error '||sqlerrm||
2010                       ' occurred in arp_process_returns.get_amount_applied');
2011    RAISE;
2012 END get_amount_applied;
2013 
2014 PROCEDURE fetch_gl_date( p_ra_rec IN ar_receivable_applications%rowtype,
2015                          p_gl_date OUT NOCOPY DATE) IS
2016   l_trx_gl_date DATE;
2017   l_rec_gl_date DATE;
2018   l_profile_appln_gl_date_def VARCHAR2(20);
2019   l_error_message VARCHAR2(128);
2020   l_defaulting_rule_used  VARCHAR2(100);
2021   l_default_gl_date DATE;
2022 BEGIN
2023 
2024    IF PG_DEBUG in ('Y', 'C') THEN
2025       arp_standard.debug('arp_process_returns.fetch_gl_date()+ ');
2026    END IF;
2027 
2028   l_profile_appln_gl_date_def := NVL(fnd_profile.value('AR_APPLICATION_GL_DATE_DEFAULT')
2029                                     , 'INV_REC_DT');
2030 
2031    IF PG_DEBUG in ('Y', 'C') THEN
2032       arp_standard.debug('Profile Value :  '||l_profile_appln_gl_date_def);
2033    END IF;
2034 
2035   BEGIN
2036     SELECT  gl_date
2037     INTO    l_trx_gl_date
2038     FROM    ra_cust_trx_line_gl_dist
2039     WHERE   customer_trx_id = p_ra_rec.applied_customer_trx_id
2040     AND     account_class = 'REC'
2041     AND     latest_rec_flag = 'Y';
2042   EXCEPTION
2043     WHEN OTHERS THEN
2044     l_trx_gl_date := NULL;
2045   END;
2046 
2047   BEGIN
2048     SELECT  gl_date
2049     INTO    l_rec_gl_date
2050     FROM    ar_cash_receipt_history
2051     WHERE   cash_receipt_id = p_ra_rec.cash_receipt_id
2052     AND     first_posted_record_flag = 'Y';
2053   EXCEPTION
2054     WHEN OTHERS THEN
2055     l_rec_gl_date := NULL;
2056   END;
2057 
2058    IF PG_DEBUG in ('Y', 'C') THEN
2059       arp_standard.debug('TRX DATE Value :  '||to_char(l_trx_gl_date));
2060       arp_standard.debug('REC DATE Value :  '||to_char(l_rec_gl_date));
2061    END IF;
2062 
2063   IF l_profile_appln_gl_date_def = 'INV_REC_SYS_DT' THEN
2064     p_gl_date := GREATEST(NVL(l_trx_gl_date, trunc(SYSDATE))
2065                           , NVL(l_rec_gl_date, trunc(SYSDATE))
2066                           , trunc(sysdate));
2067   Else
2068     /* l_profile_appln_gl_date_def = 'INV_REC_DT' */
2069     p_gl_date := GREATEST(l_trx_gl_date, l_rec_gl_date);
2070   END IF;
2071 
2072    IF PG_DEBUG in ('Y', 'C') THEN
2073       arp_standard.debug('GL DATE Before Defaulting Value :  '||to_char(p_gl_date));
2074    END IF;
2075 
2076   IF p_gl_date IS NOT NULL THEN
2077     IF ( arp_util.validate_and_default_gl_date(
2078           gl_date                => p_gl_date,
2079           trx_date               => null,
2080           validation_date1       => null,
2081           validation_date2       => null,
2082           validation_date3       => null,
2083           default_date1          => p_gl_date,
2084           default_date2          => null,
2085           default_date3          => null,
2086           p_allow_not_open_flag  => 'N',
2087           p_invoicing_rule_id    => null,
2088           p_set_of_books_id      => arp_global.set_of_books_id,
2089           p_application_id       => 222,
2090           default_gl_date        => l_default_gl_date ,
2091           defaulting_rule_used   => l_defaulting_rule_used,
2092           error_message          => l_error_message)= TRUE) THEN
2093           p_gl_date := l_default_gl_date;
2094     END IF;
2095   END IF;
2096 
2097    IF PG_DEBUG in ('Y', 'C') THEN
2098       arp_standard.debug('GL DATE OUT :  '||to_char(p_gl_date));
2099       arp_standard.debug('arp_process_returns.fetch_gl_date()-');
2100    END IF;
2101 
2102 EXCEPTION
2103 WHEN OTHERS THEN
2104    IF PG_DEBUG in ('Y', 'C') THEN
2105       arp_standard.debug('Exception -- arp_process_returns');
2106    END IF;
2107     p_gl_date := NULL;
2108 
2109 END fetch_gl_date;
2110 
2111 
2112 BEGIN
2113   initialize_globals;
2114 
2115 END arp_process_RETURNS;