DBA Data[Home] [Help]

PACKAGE BODY: APPS.ARP_CALCULATE_DISCOUNT

Source


1 PACKAGE BODY ARP_CALCULATE_DISCOUNT AS
2 /* $Header: ARRUDISB.pls 120.24.12010000.6 2009/03/06 11:29:45 mpsingh ship $ */
3 --
4 error_code                   NUMBER;
5 
6 PG_DEBUG varchar2(1) := NVL(FND_PROFILE.value('AFLOG_ENABLED'), 'N');
7 
8 /*PROCEDURE get_discount_percentages(
9     p_disc_rec IN OUT NOCOPY discount_record_type,
10     p_ps_rec IN OUT NOCOPY ar_payment_schedules%ROWTYPE
11      );
12 PROCEDURE get_payment_schedule_info(
13     p_disc_rec IN OUT NOCOPY discount_record_type,
14     p_ps_rec IN OUT NOCOPY ar_payment_schedules%ROWTYPE
15      );
16 */
17 PROCEDURE get_best_discount_percentage(
18     p_disc_rec IN OUT NOCOPY discount_record_type,
19     p_ps_rec IN ar_payment_schedules%ROWTYPE
20      );
21 
22 PROCEDURE get_current_discount_percent(
23     p_disc_rec IN OUT NOCOPY discount_record_type,
24     p_ps_rec IN ar_payment_schedules%ROWTYPE
25      );
26 
27 --PROCEDURE correct_lines_only_discounts(
28 --    p_disc_rec IN OUT NOCOPY discount_record_type,
29 --    p_ps_rec IN ar_payment_schedules%ROWTYPE );
30 PROCEDURE decrease_discounts_to_adr(
31     p_disc_rec IN OUT NOCOPY discount_record_type,
32     p_ps_rec IN ar_payment_schedules%ROWTYPE,
33     p_earned_disc IN OUT NOCOPY NUMBER,
34     p_unearned_disc IN OUT NOCOPY NUMBER);
35 --PROCEDURE determine_max_allowed_disc(
36  --   p_mode IN number,
37   --  p_disc_rec IN OUT NOCOPY discount_record_type,
38    -- p_ps_rec IN ar_payment_schedules%ROWTYPE );
39 /*FP bug 5335376 for 5223829 Leftover changes of bug for case of system option partial discount unchecked*/
40 PROCEDURE calculate_direct_discount(
41     p_mode IN number,
42     p_disc_rec IN OUT NOCOPY discount_record_type,
43     p_ps_rec IN ar_payment_schedules%ROWTYPE,
44     p_earned_disc IN OUT NOCOPY NUMBER,
45     p_unearned_disc IN OUT NOCOPY NUMBER,
46     p_called_from IN varchar2 default 'AR');
47 /*FP bug 5335376 for 5223829 Leftover changes of bug for case of system option partial discount unchecked*/
48 PROCEDURE calculate_default_discount(
49     p_mode IN number,
50     p_disc_rec IN OUT NOCOPY discount_record_type,
51     p_ps_rec IN ar_payment_schedules%ROWTYPE,
52     p_earned_disc IN OUT NOCOPY NUMBER,
53     p_unearned_disc IN OUT NOCOPY NUMBER,
54     p_out_amt_to_apply IN OUT NOCOPY NUMBER,
55     p_called_from IN varchar2 default 'AR' );
56 PROCEDURE check_input(
57     p_disc_rec IN  discount_record_type,
58     p_select_flag     IN BOOLEAN,
59     p_ps_rec IN OUT NOCOPY ar_payment_schedules%ROWTYPE );
60 PROCEDURE decrease_discounts_to_maxd(
61     p_disc_rec IN OUT NOCOPY discount_record_type,
62     p_ps_rec IN ar_payment_schedules%ROWTYPE,
63     p_earned_disc IN OUT NOCOPY NUMBER,
64     p_unearned_disc IN OUT NOCOPY NUMBER);
65 --
66 --
67 PROCEDURE validate_args_discounts_cover(
68      p_mode          IN VARCHAR2,
69      p_invoice_currency_code IN ar_cash_receipts.currency_code%TYPE,
70      p_ps_id IN ar_payment_schedules.payment_schedule_id%TYPE,
71      p_trx_date IN ar_payment_schedules.trx_date%TYPE,
72      p_apply_date IN ar_cash_receipts.receipt_date%TYPE );
73 --
74 /*===========================================================================+
75  | PROCEDURE                                                                 |
76  |    calculate_discounts                                                    |
77  |                                                                           |
78  | DESCRIPTION                                                               |
79  |    Calculate Discounts                                                    |
80  |                                                                           |
81  | SCOPE - PUBLIC                                                            |
82  |                                                                           |
83  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
84  |                                                                           |
85  | ARGUMENTS  : IN:                                                          |
86  |                      p_select_flag - Select Flag                          |
87  |                      p_mode  - Mode                                       |
88  |                                                                           |
89  |              IN OUT:                                                      |
90  |                      p_disc_rec - Discount Record                         |
91  |			p_ps_rec - Payment Schedule Record                   |
92  |									     |
93  |              OUT:                                                         |
94  | 								             |
95  | 									     |
96  | RETURNS    : NONE                                                         |
97  |                                                                           |
98  |                                                                           |
99  | NOTES                                                                     |
100  |                                                                           |
101  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
102  |  26-Feb-1998    Debbie Jancis     Added cash_receipt_id to arguments as   |
103  |                                   per cpg bug 627518.                     |
104  |  10-APR-2000    skoukunt          Fix bug 1164810, default amount applied |
105  |                                   when the profile AR: Cash Default Amount|
106  |                                   Applied OPTION set to Remaining Amount  |
107  |                                   of the Invoice                          |
108  |  04/25/02   S.Nambiar             Bug 2334691 - If the discount on partial
109  |                                   payment flag is 'Y' in system option, then
110  |                                   check the partial payment flag on payment
111  |                                   term,and take the flag from payment term. But
112  |                                   if the flag is 'N' in system option, then
113  |                                   no matter what payment term flag says,partial
114  |                                   discounts should not be allowed.        |
115  |                                   corrected the issue caused by 2144705   |
116  |                                                                           |
117  +===========================================================================*/
118 --
119 /*FP bug 5335376 for 5223829 introduced new parameters*/
120 PROCEDURE calculate_discounts (
121         p_input_amt         IN NUMBER,
122         p_grace_days         IN NUMBER,
123         p_apply_date         IN DATE,
124         p_disc_partial_pmt_flag IN VARCHAR2,
125         p_calc_disc_on_lines IN VARCHAR2,
126         p_earned_both_flag IN VARCHAR2,
127         p_use_max_cash_flag IN VARCHAR2,
128         p_default_amt_app IN VARCHAR2,
129         p_earned_disc_pct IN OUT NOCOPY NUMBER,
130         p_best_disc_pct IN OUT NOCOPY NUMBER,
131         p_out_earned_disc IN OUT NOCOPY NUMBER,
132         p_out_unearned_disc IN OUT NOCOPY NUMBER,
133         p_out_discount_date IN OUT NOCOPY DATE,
134         p_out_amt_to_apply IN OUT NOCOPY NUMBER,
135         p_close_invoice_flag IN VARCHAR2,
136         p_payment_schedule_id IN ar_payment_schedules.payment_schedule_id%TYPE,
137         p_term_id IN ar_payment_schedules.term_id%TYPE,
138         p_terms_sequence_number IN ar_payment_schedules.terms_sequence_number%TYPE,
139         p_trx_date IN ar_payment_schedules.trx_date%TYPE,
140         p_amt_due_original IN ar_payment_schedules.amount_due_original%TYPE,
141         p_amt_due_remaining IN ar_payment_schedules.amount_due_remaining%TYPE,
142         p_disc_earned IN ar_payment_schedules.discount_taken_earned%TYPE,
143         p_disc_unearned IN ar_payment_schedules.discount_taken_unearned%TYPE,
144         p_lines_original IN ar_payment_schedules.amount_line_items_original%TYPE,
145         p_invoice_currency_code IN ar_payment_schedules.invoice_currency_code%TYPE,
146 	p_select_flag     IN VARCHAR2,
147         p_mode IN NUMBER,
148         p_error_code IN OUT NOCOPY NUMBER,
149         p_cash_receipt_id IN NUMBER,
150         p_called_from IN VARCHAR2,
151         p_amt_in_dispute IN ar_payment_schedules.amount_in_dispute%TYPE) IS
152 --
153     l_ps_rec         ar_payment_schedules%ROWTYPE;
154     l_disc_rec                 discount_record_type;
155     l_select_flag                     BOOLEAN;
156     l_precision                       NUMBER;
157     l_ext_precision                   NUMBER;
158     l_min_acct_unit                   NUMBER;
159     l_format_mask		      VARCHAR2(100);
160     l_sys_disc_partial_pay_flag       VARCHAR2(1) := 'N';
161 --
162 BEGIN
163 --
164     IF PG_DEBUG in ('Y', 'C') THEN
165        arp_standard.debug(   'arp_calculate_discount.calculate_discounts() +' );
166     END IF;
167   -- ARTA Changes, calles TA version of calculate discount for TA
168   -- installation
169   IF nvl(arp_global.sysparam.ta_installed_flag,'N') = 'Y' THEN
170      NULL; -- Do Nothing
171      -- Removed ARTA changes for Bug 4936298
172   ELSE
173     IF (p_mode = AR_DIRECT_DISC OR p_mode = AR_DIRECT_NEW_DISC)
174     THEN
175         IF PG_DEBUG in ('Y', 'C') THEN
176            arp_standard.debug(   'MODE: DIRECT' );
177         END IF;
178     ELSE
179         IF PG_DEBUG in ('Y', 'C') THEN
180            arp_standard.debug(   'MODE: DEFAULT' );
181         END IF;
182     END IF;
183     IF PG_DEBUG in ('Y', 'C') THEN
184        arp_standard.debug(   'p_default_amt_app:'||p_default_amt_app );
185        arp_standard.debug(   'p_earned_both_flag:'||p_earned_both_flag );
186        arp_standard.debug(   'p_earned_disc_pct:'||p_earned_disc_pct );
187     END IF;
188     --
189     l_disc_rec.input_amt := p_input_amt;
190     IF PG_DEBUG in ('Y', 'C') THEN
191        arp_standard.debug(   'Input amt = '||TO_CHAR( p_input_amt ) );
192     END IF;
193     --IF ( p_grace_days IS  NOT NULL ) THEN
194     l_disc_rec.grace_days := p_grace_days;
195     --END IF;
196     l_disc_rec.apply_date := p_apply_date;
197     l_disc_rec.disc_partial_pmt_flag := p_disc_partial_pmt_flag;
198     l_disc_rec.calc_disc_on_lines := p_calc_disc_on_lines;
199     l_disc_rec.earned_both_flag := p_earned_both_flag;
200     l_disc_rec.use_max_cash_flag := p_use_max_cash_flag;
201     l_disc_rec.default_amt_app := p_default_amt_app;
202     l_disc_rec.earned_disc_pct := p_earned_disc_pct;
203     l_disc_rec.best_disc_pct := p_best_disc_pct;
204     l_disc_rec.out_earned_disc := p_out_earned_disc;
205     l_disc_rec.out_unearned_disc := p_out_unearned_disc;
206     l_disc_rec.out_discount_date := p_out_discount_date;
207     l_disc_rec.out_amt_to_apply := p_out_amt_to_apply;
208     l_disc_rec.close_invoice_flag := p_close_invoice_flag;
209     l_ps_rec.payment_schedule_id := p_payment_schedule_id;
210     l_ps_rec.term_id := p_term_id;
211     l_ps_rec.terms_sequence_number := p_terms_sequence_number;
212     l_ps_rec.trx_date := p_trx_date;
213     l_ps_rec.amount_due_original := p_amt_due_original;
214     l_ps_rec.amount_due_remaining := p_amt_due_remaining;
215     l_ps_rec.discount_taken_earned := p_disc_earned;
216     l_ps_rec.discount_taken_unearned :=  p_disc_unearned;
217     l_ps_rec.amount_line_items_original := p_lines_original;
218     l_ps_rec.invoice_currency_code := p_invoice_currency_code;
219     l_ps_rec.payment_schedule_id := p_payment_schedule_id;
220 /*FP bug 5335376 for Bug 5223829 set the values as per call from iReceivables*/
221     IF p_called_from = 'OIR' Then
222       l_ps_rec.amount_in_dispute := p_amt_in_dispute;
223     END IF;
224 
225 
226     IF PG_DEBUG in ('Y', 'C') THEN
227        arp_standard.debug(   'p_close_invoice_flag:'||p_close_invoice_flag );
228     END IF;
229 
230     -- Check input(ardckin). Exit with error if not all needed fields are
231     -- populated.
232          IF PG_DEBUG in ('Y', 'C') THEN
233             arp_standard.debug(   'error_code = '||TO_CHAR( error_code ));
234          END IF;
235     --   p_error_code := AR_M_FAILURE ;
236     --   arp_standard.debug( 'p_error_code = '||TO_CHAR( p_error_code )) ;
237     --   RETURN;
238 
239     IF PG_DEBUG in ('Y', 'C') THEN
240        arp_standard.debug(   'l_ps_rec.amount_due_remaining := '||
241 		TO_CHAR(l_ps_rec.amount_due_remaining ));
242     END IF;
243 
244     IF (p_select_flag = 'Y')
245     THEN
246         IF PG_DEBUG in ('Y', 'C') THEN
247            arp_standard.debug(   'l_select_flag: TRUE' );
248         END IF;
249         l_select_flag := TRUE;
250         get_payment_schedule_info ( l_disc_rec, l_ps_rec );
251     ELSE
252         IF PG_DEBUG in ('Y', 'C') THEN
253            arp_standard.debug(   'l_select_flag: FALSE' );
254         END IF;
255         l_select_flag := FALSE;
256     END IF;
257 
258     check_input( l_disc_rec, l_select_flag, l_ps_rec) ;
259 
260     -- 1/29/1996 H.Kaukovuo	Removed p_select_flag
261     get_discount_percentages (l_disc_rec, l_ps_rec);
262 
263     -- Correct percentages for lines-only(ardline) discount if necessary.
264     IF l_disc_rec.calc_disc_on_lines <> 'I' AND
265        l_disc_rec.calc_disc_on_lines <> 'N'
266     THEN
267         correct_lines_only_discounts ( l_disc_rec, l_ps_rec );
268     END IF;
269     --
270     -- If no discount percentages, set discounts to zero.
271     IF ( l_disc_rec.best_disc_pct = 0 ) THEN
272         p_out_earned_disc := 0 ;
273         p_out_unearned_disc := 0 ;
274         l_disc_rec.earned_disc_pct := 0;
275         --
276         -- If in direct calculation mode, exit now.
277         IF  p_mode = AR_DIRECT_DISC OR p_mode = AR_DIRECT_NEW_DISC
278         THEN
279             p_earned_disc_pct := l_disc_rec.earned_disc_pct;
280             p_best_disc_pct := l_disc_rec.best_disc_pct;
281             p_out_discount_date := l_disc_rec.out_discount_date;
282             --p_error_code := AR_M_SUCCESS;
283             RETURN;
284         END IF;
285     --
286     END IF;
287     --
288     -- Calculate maximum remaining discount(ardmaxd) that may be taken for
289     -- this ps.
290     determine_max_allowed_disc ( p_mode, l_disc_rec, l_ps_rec );
291     IF PG_DEBUG in ('Y', 'C') THEN
292        arp_standard.debug(   'l_disc_rec.max_disc = '||
293                          TO_CHAR( l_disc_rec.max_disc ) );
294     END IF;
295     --
296     --
297     -- Calculate discount amounts(ardcdir and ardcdef).
298     IF ( p_mode = AR_DIRECT_DISC OR p_mode = AR_DIRECT_NEW_DISC ) THEN
299       -- Added the condition to fix bug 1236196
300       IF l_disc_rec.max_disc = 0 THEN
301          p_out_earned_disc := 0;
302          p_out_unearned_disc := 0;
303       ELSE
304       /*FP bug 5335376 for Bug 5223829 Leftover changes of bug for case of system option partial discount unchecked*/
305         calculate_direct_discount ( p_mode,
306                                     l_disc_rec,
307                                     l_ps_rec,
308                                     p_out_earned_disc, p_out_unearned_disc,p_called_from );
309       /*Start FP Bug-5741063 Base Bug- 53866459 extended fix to call procedure to decrease discount as per max allowed */
310         decrease_discounts_to_maxd(l_disc_rec, l_ps_rec, p_out_earned_disc,p_out_unearned_disc );
311       END IF;
312     ELSIF ( p_mode = AR_DEFAULT_DISC OR p_mode = AR_DEFAULT_NEW_DISC) THEN
313 /*FP bug 5335376 for Bug  5223829 Leftover changes of bug for case of system option partial discount unchecked
314   Passed newly introduced parameter p_called_from*/
315 
316         calculate_default_discount ( p_mode,
317                                      l_disc_rec,
318                                      l_ps_rec,
319                                      p_out_earned_disc, p_out_unearned_disc,
320                                      p_out_amt_to_apply,p_called_from );
321         /*Start FP Bug-5741063 Bug 5386459 extended fix to call procedure to decrease discount as per max allowed */
322         decrease_discounts_to_maxd(l_disc_rec, l_ps_rec, p_out_earned_disc,p_out_unearned_disc );
323         --
324         IF PG_DEBUG in ('Y', 'C') THEN
325            arp_standard.debug(   'p_out_earned_disc = '||TO_CHAR( p_out_earned_disc ));
326            arp_standard.debug(   'p_out_unearned_disc = '||TO_CHAR( p_out_unearned_disc ));
327            arp_standard.debug(   'p_out_amt_to_apply = '||TO_CHAR( p_out_amt_to_apply ));
328         END IF;
329     --
330     ELSE
331         IF PG_DEBUG in ('Y', 'C') THEN
332            arp_standard.debug(   'Unknown Mode ' );
333         END IF;
337     END IF;
334         RAISE ar_m_fail;
335         --p_error_code := AR_M_FAILURE ;
336         --RETURN;
338     --
339     -- Decrease the discounts as necessary to avoid overpaying, to a limit
340     -- of zero(ardadr). This is not necessary in default mode.
341     IF ( (p_mode = AR_DIRECT_DISC OR p_mode = AR_DIRECT_NEW_DISC) AND
342          l_disc_rec.use_max_cash_flag = 'Y' ) THEN
343         decrease_discounts_to_adr ( l_disc_rec,
344                                     l_ps_rec,
345                                     p_out_earned_disc, p_out_unearned_disc);
346     END IF;
347     --
348     SELECT DECODE( fc.minimum_accountable_unit,
349                    NULL, ROUND( p_out_earned_disc, fc.precision ),
350                    ROUND( p_out_earned_disc/fc.minimum_accountable_unit ) *
351                         ( fc.minimum_accountable_unit )
352                  ),
353            DECODE( fc.minimum_accountable_unit,
354                    NULL, ROUND( p_out_unearned_disc, fc.precision ),
355                    ROUND( p_out_unearned_disc/fc.minimum_accountable_unit ) *
356                         ( fc.minimum_accountable_unit )
357                  ),
358            DECODE( fc.minimum_accountable_unit,
359                    NULL, ROUND( p_out_amt_to_apply, fc.precision ),
360                    ROUND( p_out_amt_to_apply/fc.minimum_accountable_unit ) *
361                         ( fc.minimum_accountable_unit )
362                  )
363     INTO p_out_earned_disc,
364          p_out_unearned_disc,
365          p_out_amt_to_apply
366     FROM fnd_currencies fc
367     WHERE fc.currency_code = l_ps_rec.invoice_currency_code;
368     --
369     IF  (p_mode = AR_DEFAULT_DISC OR p_mode = AR_DEFAULT_NEW_DISC)
370     THEN
371         IF PG_DEBUG in ('Y', 'C') THEN
372            arp_standard.debug(   'amt_due_remaining = '||TO_CHAR( l_ps_rec.amount_due_remaining ) );
373         END IF;
374         -- Fix bug 1164810, default amount applied when the profile
375         -- AR: Cash - Default Amount Applied OPTION is set to
376         -- Remaining Amount of the Invoice
377         IF p_default_amt_app <> 'PMT' and p_close_invoice_flag = 'Y'
378         THEN
379           IF ( p_input_amt < 0 ) THEN
380             p_out_amt_to_apply := l_ps_rec.amount_due_remaining - p_out_earned_disc;
381           ELSE
382 	  -- Fix bug 1662462 , default amount applied when the profile
383 	  -- AR: Cash -Default Amount Applied OPTION is set to
384 	  -- Remaining Amount of the invoice and the input amount
385 	  -- is positive
386             IF (l_ps_rec.amount_due_remaining - p_out_earned_disc) <= p_input_amt
387             THEN
388                 p_out_amt_to_apply := l_ps_rec.amount_due_remaining - p_out_earned_disc;
389             ELSE
390                 --
391                 -- p_amt_due_remaining >= p_input_amt
392                 --
393                   --  p_out_amt_to_apply := p_input_amt - p_out_earned_disc;
394                 --begin 2144705
395                      p_out_amt_to_apply := p_input_amt ;
396 
397                 /*For bug 2147188 populating the  partial_pmt_flag correctly to
398                   calculate the discount correctly*/
399 
400                 SELECT arp_standard.sysparm.partial_discount_flag
401 		INTO l_sys_disc_partial_pay_flag
402 		FROM dual;
403 
404                /*--------------------------------------------------------------------+
405                 |Bug 2334691 - If partial discount flag in system option is 'N' then |
406                 |l_disc_rec.disc_partial_pmt_flag= 'N' , if discount flag is 'Y' on  |
407                 |system option, then take the value from payment terms record        |
408                 *--------------------------------------------------------------------*/
409 
410                 IF PG_DEBUG in ('Y', 'C') THEN
411                    arp_standard.debug(   'Partial Discount flag System Options = '|| l_sys_disc_partial_pay_flag);
412 	           arp_standard.debug(   'Partial Discount flag Payment Term = '|| l_disc_rec.disc_partial_pmt_flag);
413 	        END IF;
414 
415                 IF NVL(l_sys_disc_partial_pay_flag,'N') = 'N' THEN
416                    l_disc_rec.disc_partial_pmt_flag := 'N';
417                 ELSE
418                      null;
419                 END IF;
420 
421                 IF PG_DEBUG in ('Y', 'C') THEN
422                    arp_standard.debug(   'Partial Discount flag - Final  = '|| l_disc_rec.disc_partial_pmt_flag);
423                 END IF;
424 
425                 IF NVL(l_disc_rec.disc_partial_pmt_flag,'N')= 'Y' then
426                  SELECT DECODE( fc.minimum_accountable_unit,
427                         NULL, ROUND( ((p_out_earned_disc/(l_ps_rec.amount_due_remaining-p_out_earned_disc))
428                                                                         *p_input_amt), fc.precision ),
429                           ROUND( ((p_out_earned_disc/(l_ps_rec.amount_due_remaining-p_out_earned_disc))
430                                                                          *p_input_amt)
431                                    /fc.minimum_accountable_unit ) *
432                                ( fc.minimum_accountable_unit )
433                             )
434                  INTO p_out_earned_disc
435                  FROM fnd_currencies fc
436                  WHERE fc.currency_code = l_ps_rec.invoice_currency_code;
437                else
438                   p_out_earned_disc :=0;
439                end if;
440                 --end 2144705
441             END IF;
442           END IF;
446         -- ignore the input amount if the close invoice flag = 'Y'
443         -- Not sure if at anytime the control comes to the below conditions
444         ELSIF  p_close_invoice_flag = 'Y'
445         THEN
447             p_out_amt_to_apply := l_ps_rec.amount_due_remaining - p_out_earned_disc;
448         ELSIF p_default_amt_app <> 'PMT'
449         THEN
450             IF l_ps_rec.amount_due_remaining < p_input_amt
451             THEN
452                 p_out_amt_to_apply := l_ps_rec.amount_due_remaining - p_out_earned_disc;
453             ELSE
454                 --
455                 -- p_amt_due_remaining >= p_input_amt
456                 --
457                     p_out_amt_to_apply := p_input_amt - p_out_earned_disc;
458             END IF;
459         END IF;
460 
461 /*
462         -- ignore the input amount if the close invoice flag = 'Y'
463         IF p_close_invoice_flag = 'Y'
464         THEN
465             p_out_amt_to_apply := l_ps_rec.amount_due_remaining - p_out_earned_disc;
466         ELSIF p_default_amt_app <> 'PMT'
467         THEN
468             IF l_ps_rec.amount_due_remaining < p_input_amt
469             THEN
470                 p_out_amt_to_apply := l_ps_rec.amount_due_remaining - p_out_earned_disc;
471             ELSE
472                 --
473                 -- p_amt_due_remaining >= p_input_amt
474                 --
475                     p_out_amt_to_apply := p_input_amt - p_out_earned_disc;
476             END IF;
477         END IF;
478 */
479     END IF;
480     --
481     IF PG_DEBUG in ('Y', 'C') THEN
482        arp_standard.debug(   'earned_disc = '||TO_CHAR( p_out_earned_disc ) );
483        arp_standard.debug(   'Unearned_disc = '||TO_CHAR( p_out_unearned_disc ) );
484        arp_standard.debug(   'Amount to Apply = '||TO_CHAR( p_out_amt_to_apply ) );
485     END IF;
486     --
487     p_earned_disc_pct := l_disc_rec.earned_disc_pct;
488     p_best_disc_pct := l_disc_rec.best_disc_pct;
489     p_out_discount_date := l_disc_rec.out_discount_date;
490     --p_error_code := AR_M_SUCCESS;
491     IF PG_DEBUG in ('Y', 'C') THEN
492        arp_standard.debug(   'p_error_code := '||p_error_code );
493     END IF;
494   END IF;
495     IF PG_DEBUG in ('Y', 'C') THEN
496        arp_standard.debug(   'arp_calculate_discount.calculate_discounts() -' );
497     END IF;
498     --
499     EXCEPTION
500     	WHEN OTHERS THEN
501            IF PG_DEBUG in ('Y', 'C') THEN
502               arp_standard.debug(   'Exception: arp_calculate_discount.calculate_discounts()' );
503            END IF;
504         --IF (error_code IS NOT NULL) THEN
505         --p_error_code := error_code;
506         --RETURN;
507         --ELSE
508 	   RAISE;
509         --END IF;
510 END calculate_discounts;
511 --
512 --
513 /*===========================================================================+
514  | PROCEDURE                                                                 |
515  |    get_discount_percentages                                               |
516  |                                                                           |
517  | DESCRIPTION                                                               |
518  |    Get Discount Percentages                                               |
519  |                                                                           |
520  | SCOPE - PRIVATE                                                           |
521  |                                                                           |
522  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
523  |                                                                           |
524  | ARGUMENTS  : IN:                                                          |
525  |                                                                           |
526  |              IN OUT:                                                      |
527  |                      p_disc_rec - Discount Record                  |
528  |                      p_ps_rec - Payment Schedule Record  |
529  |								             |
530  |              OUT:                          			             |
531  |								             |
532  | RETURNS    : NONE                                                         |
533  |                                                                           |
534  |                                                                           |
535  | NOTES                                                                     |
536  |                                                                           |
537  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
538  | 1/29/1996	Harri Kaukovuo	Modified comments and clarified program
539  |				out NOCOPY look. Removed obsolete parameter
540  |				P_SELECT_FLAG.
541  +===========================================================================*/
542 PROCEDURE get_discount_percentages(
543     p_disc_rec  	IN OUT NOCOPY arp_calculate_discount.discount_record_type,
544     p_ps_rec    	IN OUT NOCOPY ar_payment_schedules%ROWTYPE
545      ) IS
546 BEGIN
547     IF PG_DEBUG in ('Y', 'C') THEN
548        arp_standard.debug(   'arp_calculate_discount.'||
549 		'get_discount_percentages()+' );
550     END IF;
551 
552     -- ----------------------------------------------------------------
553     -- Get the best discount percentage.
554     -- ----------------------------------------------------------------
555     get_best_discount_percentage (p_disc_rec, p_ps_rec);
556 
557     -- ----------------------------------------------------------------
561     IF (p_disc_rec.best_disc_pct = 0)
558     -- If best percent is zero, return zero also for earned discount.
559     -- (Avoid unnecessary discount fetch in get_current_discount_percent)
560     -- ----------------------------------------------------------------
562     THEN
563       p_disc_rec.earned_disc_pct := 0;
564     ELSE       -- used to be ELSIF p_disc_rec.earned_disc_pct IS NULL THEN
565       get_current_discount_percent (p_disc_rec, p_ps_rec);
566     END IF;
567 
568     IF PG_DEBUG in ('Y', 'C') THEN
569        arp_standard.debug( 'arp_calculate_discount.get_discount_percentages()-');
570     END IF;
571     EXCEPTION
572         WHEN OTHERS THEN
573            IF PG_DEBUG in ('Y', 'C') THEN
574               arp_standard.debug(   'Exception: arp_calculate_discount.'||
575 			'get_discount_percentages()' );
576            END IF;
577            RAISE;
578 END get_discount_percentages;
579 --
580 /*===========================================================================+
581  | PROCEDURE                                                                 |
582  |    get_payment_schedule_info                                              |
583  |                                                                           |
584  | DESCRIPTION                                                               |
585  |    Select Payment Schedule info and populate payment schedule record and  |
586  |    two discount record values (calc_disc_on_lines and discount_  |
587  |    partial_payment_flag.                                                  |
588  | 									     |
589  |								             |
590  | SCOPE - PRIVATE                                                           |
591  |                                                                           |
592  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
593  |                                                                           |
594  | ARGUMENTS  : IN:                                                          |
595  |                                                                           |
596  |              IN OUT:                                                      |
597  |                      p_disc_rec - Discount Record                  |
598  |                      p_ps_rec - Payment Schedule Record  |
599  |									     |
600  |		OUT:							     |
601  |                                                                           |
602  | RETURNS    : NONE                                                         |
603  |                                                                           |
604  |                                                                           |
605  | NOTES                                                                     |
606  |                                                                           |
607  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
608  |                                                                           |
609  +===========================================================================*/
610 PROCEDURE get_payment_schedule_info(
611     p_disc_rec IN OUT NOCOPY arp_calculate_discount.discount_record_type,
612     p_ps_rec IN OUT NOCOPY ar_payment_schedules%ROWTYPE
613      ) IS
614 l_payment_schedule_id NUMBER;
615 BEGIN
616     IF PG_DEBUG in ('Y', 'C') THEN
617        arp_standard.debug( 'arp_calculate_discount.get_payment_schedule_info() +' );
618     END IF;
619     --
620     -- Select Payment Schedule info and populate ps record type and two disc record
621     -- values (calc_disc_on_lines and disc_partial_pmt_flag)
622     --
623     l_payment_schedule_id := p_ps_rec.payment_schedule_id;
624     BEGIN
625          SELECT ps.term_id,
626                 ps.terms_sequence_number,
627                 ps.trx_date,
628                 ps.amount_due_original,
629                 ps.amount_due_remaining,
630                 NVL(ps.discount_taken_earned, 0),
631                 NVL(ps.discount_taken_unearned, 0),
632                 NVL(ps.amount_line_items_original, 0),
633                 ps.invoice_currency_code,
634                 ps.amount_in_dispute, /*FP Bug 5335376 for Bug 5223829 assign value of dispute*/
635                 t.calc_discount_on_lines_flag,
636                 t.partial_discount_flag
637          INTO   p_ps_rec.term_id,
638                 p_ps_rec.terms_sequence_number,
639                 p_ps_rec.trx_date,
640                 p_ps_rec.amount_due_original,
641                 p_ps_rec.amount_due_remaining,
642                 p_ps_rec.discount_taken_earned,
643                 p_ps_rec.discount_taken_unearned,
644                 p_ps_rec.amount_line_items_original,
645                 p_ps_rec.invoice_currency_code,
646                 p_ps_rec.amount_in_dispute,/*FP 5335376 for Bug 5223829 assign value of dispute*/
647                 p_disc_rec.calc_disc_on_lines,
648                 p_disc_rec.disc_partial_pmt_flag
649          FROM   ar_payment_schedules ps, ra_terms t
650          WHERE  ps.payment_schedule_id = l_payment_schedule_id
651            AND  ps.term_id = t.term_id(+);
652 
653          EXCEPTION
654              WHEN NO_DATA_FOUND THEN
655              --error_code := AR_M_NO_RECORD ;
656                  IF PG_DEBUG in ('Y', 'C') THEN
657                     arp_standard.debug('get_payment_schedule_info: ' ||  'No data found in ar_payment_schedules' );
658                  END IF;
659                    RAISE ar_m_no_rec;
660              WHEN OTHERS THEN
664                  END IF;
661                  IF PG_DEBUG in ('Y', 'C') THEN
662                     arp_standard.debug('get_payment_schedule_info: ' ||
663                        'EXCEPTION: arp_calculate_discount.get_payment_schedule_info' );
665               RAISE;
666     END;
667 
668     IF ( p_ps_rec.term_id IS NULL ) THEN
669          p_ps_rec.term_id := AR_NO_TERM;
670     END IF;
671 
672     IF ( p_ps_rec.terms_sequence_number IS NULL ) THEN
673          p_ps_rec.terms_sequence_number := AR_NO_TERM;
674     END IF;
675 
676     IF PG_DEBUG in ('Y', 'C') THEN
677        arp_standard.debug( 'arp_calculate_discount.get_payment_schedule_info()-');
678     END IF;
679 
680     EXCEPTION
681         WHEN OTHERS THEN
682            IF PG_DEBUG in ('Y', 'C') THEN
683               arp_standard.debug('get_payment_schedule_info: ' ||  'Exception: arp_calculate_discount.'||
684 		'get_payment_schedule_info()' );
685            END IF;
686            RAISE;
687 END get_payment_schedule_info;
688 --
689 /*===========================================================================+
690  | PROCEDURE                                                                 |
691  |    get_best_discount_percentage                                           |
692  |                                                                           |
693  | DESCRIPTION                                                               |
694  |    Get Best Discount Percentage                                           |
695  |                                                                           |
696  | SCOPE - PRIVATE                                                           |
697  |                                                                           |
698  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
699  |                                                                           |
700  | ARGUMENTS  : IN:                                                          |
701  |                      p_ps_rec - Payment Schedule Record  |
702  |              							     |
703  |              IN OUT:                                                      |
704  |                      p_disc_rec - Discount Record                  |
705  |                                                                           |
706  |              OUT:                                                         |
707  |                                                                           |
708  | RETURNS    : NONE                                                         |
709  |                                                                           |
710  |                                                                           |
711  | NOTES                                                                     |
712  |                                                                           |
713  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
714  | 29/1/1996	Harri Kaukovuo		Removed IF statements to check whether
715  |					returned value is null and replaced
716  |					NVL(<value>,0) instead into SELECT.
717  +===========================================================================*/
718 PROCEDURE get_best_discount_percentage(
719     p_disc_rec 	IN OUT NOCOPY discount_record_type,
720     p_ps_rec 	IN ar_payment_schedules%ROWTYPE
721      ) IS
722 BEGIN
723     IF PG_DEBUG in ('Y', 'C') THEN
724        arp_standard.debug(   'arp_calculate_discount.'||
725 		'get_best_discount_percentage()+' );
726     END IF;
727     --
728     -- Get best discount percentage
729     --
730 
731     SELECT NVL(MAX(discount_percent),0) * 0.01
732     INTO   p_disc_rec.best_disc_pct
733     FROM   RA_TERMS_LINES_DISCOUNTS tld
734     WHERE
735 	tld.term_id 		= p_ps_rec.term_id
736     AND tld.sequence_num 	= p_ps_rec.terms_sequence_number;
737 
738     IF PG_DEBUG in ('Y', 'C') THEN
739        arp_standard.debug(   '-- best_discount_percentage:'||
740 	TO_CHAR( p_disc_rec.best_disc_pct ) );
741        arp_standard.debug(   'arp_calculate_discount.'||
742 	'get_best_discount_percentage()-' );
743     END IF;
744 
745     EXCEPTION
746         WHEN OTHERS THEN
747            IF PG_DEBUG in ('Y', 'C') THEN
748               arp_standard.debug(   'Exception: arp_calculate_discount.'||
749 			'get_best_discount_percentage()' );
750            END IF;
751            RAISE;
752 END get_best_discount_percentage;
753 --
754 /*===========================================================================+
755  | PROCEDURE                                                                 |
756  |    get_current_discount_percent                                           |
757  |                                                                           |
758  | DESCRIPTION                                                               |
759  |    Get Current Discount Percentage                                        |
760  |                                                                           |
761  | SCOPE - PRIVATE                                                           |
762  |                                                                           |
763  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
764  |                                                                           |
765  | ARGUMENTS  : IN:                                                          |
766  |                      p_ps_rec - Payment Schedule Record  |
767  |                                                                           |
771  |              OUT:                                                         |
768  |              IN OUT:                                                      |
769  |                      p_disc_rec - Discount Record                  |
770  |                                                                           |
772  |                                                                           |
773  | RETURNS    : NONE                                                         |
774  |
775  |
776  | NOTES
777  |	Note that this routine has changed from the original and requires
778  |	view AR_TRX_DISCOUNTS_V.
779  |	This view should be defined in file arvrdisc.sql
780  |
781  | MODIFICATION HISTORY -
782  | 5/24/1995	Created by Shiv Ragunat
783  | 1/29/1996	Harri Kaukovuo	Changed routine to use view
784  |				AR_TRX_DISCOUNTS_V to centralize
785  |				discount calculation.
786  | 3/28/1996	H.Kaukovuo	Finished the changes.
787  +===========================================================================*/
788 
789 PROCEDURE get_current_discount_percent(
790     p_disc_rec 		IN OUT NOCOPY discount_record_type,
791     p_ps_rec 		IN ar_payment_schedules%ROWTYPE
792      ) IS
793 
794 l_terms_sequence_number	NUMBER;
795 l_term_id 		NUMBER;
796 l_grace_days 		NUMBER;
797 l_trx_date 		DATE;
798 l_apply_date 		DATE;
799 l_calculated_date	DATE;
800 
801 -- This cursor will return all possible discounts for selected
802 -- transaction
803 CURSOR c_discounts(p_calculated_date in date) IS
804 	SELECT
805 		td.discount_percent
806 	,	td.discount_date
807 	FROM	ar_trx_discounts_v	td
808 	WHERE
809 		td.payment_schedule_id	= p_ps_rec.payment_schedule_id
810 	AND	p_calculated_date <= td.discount_date
811 	ORDER BY
812 	td.discount_date	ASC;
813 
814 BEGIN
815     IF PG_DEBUG in ('Y', 'C') THEN
816        arp_standard.debug(
817 	'arp_calculate_discount.get_current_discount_percent()+' );
818     END IF;
819     --
820     -- Get current discount percentage
821     --
822 --7693172
823     l_grace_days 		:= NVL(p_disc_rec.grace_days,0);
824     l_apply_date 		:= p_disc_rec.apply_date;
825     l_calculated_date		:= TRUNC(l_apply_date - l_grace_days);
826 
827     IF PG_DEBUG in ('Y', 'C') THEN
828        arp_standard.debug(   '-- l_grace_days := '||TO_CHAR(l_grace_days ));
829        arp_standard.debug(   '-- l_apply_date :='||TO_CHAR(l_apply_date,'DD-MON-RRRR HH24:MI:SS' ));
830        arp_standard.debug(   '-- l_calculated_date :='||TO_CHAR(l_calculated_date,'DD-MON-RRRR HH24:MI:SS' ));
831     END IF;
832 
833     -- If cursor does not return anything, this will be the default
834     p_disc_rec.earned_disc_pct := 0;
835 
836     -- Get the first row, that should be the closest discount date
837     FOR rc_discounts IN c_discounts(l_calculated_date) LOOP
838         p_disc_rec.earned_disc_pct := rc_discounts.discount_percent*0.01;
839         p_disc_rec.out_discount_date := rc_discounts.discount_date;
840         EXIT;
841     END LOOP;
842 
843     IF PG_DEBUG in ('Y', 'C') THEN
844        arp_standard.debug(  '--p_disc_rec.earned_disc_pct:'||
845 	TO_CHAR(p_disc_rec.earned_disc_pct));
846        arp_standard.debug(   'arp_calculate_discount.'||
847 	'get_current_discount_percent()-' );
848     END IF;
849 
850     EXCEPTION
851       WHEN OTHERS THEN
852         IF PG_DEBUG in ('Y', 'C') THEN
853            arp_standard.debug(   'EXCEPTION: arp_calculate_discount.'||
854 		'get_current_discount_percent()' );
855         END IF;
856         RAISE;
857 
858 END get_current_discount_percent;
859 
860 /*===========================================================================+
861  | PROCEDURE                                                                 |
862  |    correct_lines_only_discounts                                           |
863  |                                                                           |
864  | DESCRIPTION                                                               |
865  |    Correct Discount Percentages for LINEs-only discounts.                 |
866  |                                                                           |
867  | SCOPE - PRIVATE                                                           |
868  |                                                                           |
869  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
870  |                                                                           |
871  | ARGUMENTS  : IN:                                                          |
872  |                      p_ps_rec - Payment Schedule Record                   |
873  |                                                                           |
874  |              IN OUT:                                                      |
875  |                      p_disc_rec - Discount Record                         |
876  |                                                                           |
877  |              OUT:                                                         |
878  |                                                                           |
879  | RETURNS    : NONE                                                         |
880  |                                                                           |
881  |                                                                           |
882  | NOTES                                                                     |
883  |                                                                           |
887  |                              'T' adjusts the discount multiplier to       |
884  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
885  |                                                                           |
886  |	T Schraid - 7/26/96	Added 2 new discount bases: 'T' and 'F'.     |
888  |                              include amounts on all invoice lines and     |
889  |                              their tax.                                   |
890  |                              'F' adjusts the discount multiplier to       |
891  |                              include amounts on all invoice lines that    |
892  |                              are not 'Freight' item and their tax.        |
893  |      V Ahluwalia 05/18/98    Bug #592696, if amount due original is 0 then|
894  |                              discount percent is 0, prevent division by 0 |
895  +===========================================================================*/
896 PROCEDURE correct_lines_only_discounts(
897     p_disc_rec IN OUT NOCOPY arp_calculate_discount.discount_record_type,
898     p_ps_rec IN ar_payment_schedules%ROWTYPE ) IS
899     l_line_adjusted  NUMBER;
900     l_line_applied NUMBER;
901     l_amount_adjusted NUMBER;
902     l_amount_applied NUMBER;
903     l_adjustments BOOLEAN;
904     l_credit_memos BOOLEAN;
905     l_numerator NUMBER;
906     l_denominator NUMBER;
907     l_multiplier NUMBER(25,10);
908     l_inventory_item_id  NUMBER;
909 --
910 --  new variables for the discount bases : 'T' and 'F'
911 --
912     l_tax_original  NUMBER;
913     l_tax_adjustments  BOOLEAN;
914     l_tax_credit_memos  BOOLEAN;
915     l_tax_line_adjusted  NUMBER;
916     l_tax_line_applied  NUMBER;
917     l_freight_original  NUMBER;
918 
919 --
920 BEGIN
921     IF PG_DEBUG in ('Y', 'C') THEN
922        arp_standard.debug( 'arp_calculate_discount.correct_lines_only_discounts() +' );
923     END IF;
924     --
925     --Correct discount percentages for LINEs only discounts.
926     --
927     l_adjustments := TRUE;
928     l_tax_adjustments := TRUE;
929     l_credit_memos := TRUE;
930     l_tax_credit_memos := TRUE;
931     --
932     BEGIN
933         SELECT nvl(sum(line_adjusted),0), sum(amount), nvl(sum(tax_adjusted),0)
934                INTO l_line_adjusted, l_amount_adjusted, l_tax_line_adjusted
935                FROM AR_ADJUSTMENTS
936               WHERE payment_schedule_id = p_ps_rec.payment_schedule_id
937                 AND status = 'A';
938     END;
939     --
940     IF ( l_amount_adjusted IS NULL ) THEN
941         IF PG_DEBUG in ('Y', 'C') THEN
942            arp_standard.debug( 'arp_calculate_discount.correct_lines_only_discounts  : No adjustments for payment schedule' );
943         END IF;
944         l_adjustments := FALSE;
945 	l_tax_adjustments := FALSE;
946     END IF;
947     --
948     BEGIN
949         SELECT nvl(sum(line_applied),0), sum(amount_applied),
950 	       nvl(sum(tax_applied),0)
951                INTO l_line_applied, l_amount_applied, l_tax_line_applied
952                FROM AR_RECEIVABLE_APPLICATIONS
953                WHERE application_type = 'CM'
954                AND applied_payment_schedule_id = p_ps_rec.payment_schedule_id
955                AND status = 'APP'
956                AND application_rule in ('65','66','67');
957     END;
958     --
959     IF ( l_amount_applied IS NULL ) THEN
960         IF PG_DEBUG in ('Y', 'C') THEN
961            arp_standard.debug( 'arp_calculate_discount.correct_lines_only_discounts  : No credit memos for payment schedule' );
962         END IF;
963         l_credit_memos := FALSE;
964         l_tax_credit_memos := FALSE;
965     END IF;
966 
967     --set numerator = LINES_ORIGINAL + sum(LINE_ADJUSTED) - sum(RA LINE CM)
968     --and the denominator = ADO + sum(AMOUNT_ADJUSTED) - sum(RA CM)  */
969 
970     -- If discount basis = 'F' then get amounts on non-freight item lines,
971     -- i.e. lines where the inventory item id is not the same as the one
972     -- defined in profile option Tax: Inventory Item for Freight.
973 
974     IF (p_disc_rec.calc_disc_on_lines IN ('L','F'))
975     THEN
976 
977     -- OE/OM change
978       fnd_profile.get('ZX_INVENTORY_ITEM_FOR_FREIGHT', l_inventory_item_id);
979 
980 
981       IF l_inventory_item_id IS NOT NULL  THEN
982 
983         BEGIN
984 
985           /* 7659455 - We now calculate numerator for both L and F here.
986              L is line-only so line_type must = LINE.
987              F is both line and tax, so we sum all returned rows.
988 
989              Freight rows are always excluded (by where clause)
990 
991               IF line_type = LINE,
992                  return extended_amount
993               ELSE
994                  IF calc_disc_on_lines = F (Lines + Tax, not Freight + Tax)
995                     return extended_amount
996                  ELSE
997                     return zero (for this line)
998                  END IF
999               END IF
1000           */
1001 
1002 	  SELECT nvl(sum(
1003                  DECODE(rctl.line_type, 'LINE', rctl.extended_amount,
1004                           DECODE(p_disc_rec.calc_disc_on_lines, 'F',
1005                                     rctl.extended_amount, 0))),0)
1006 	  INTO   l_numerator
1007           FROM
1008              ra_customer_trx_lines rctl,
1009              ar_payment_schedules ps
1010           WHERE
1014           NOT IN (
1011                 rctl.line_type IN ('LINE','TAX')
1012           AND   nvl(rctl.inventory_item_id,-1) <> l_inventory_item_id
1013           AND   nvl(rctl.link_to_cust_trx_line_id,-1)
1015                 SELECT  rctl2.customer_trx_line_id
1016                 FROM
1017                         ra_customer_trx_lines  rctl2,
1018                         ar_payment_schedules  ps2
1019                 WHERE
1020                         nvl(rctl2.inventory_item_id,-1) = l_inventory_item_id
1021                 AND     rctl2.customer_trx_id = ps2.customer_trx_id
1022                 AND     ps2.payment_schedule_id = p_ps_rec.payment_schedule_id
1023                 )
1024           AND   rctl.customer_trx_id = ps.customer_trx_id
1025           AND   ps.payment_schedule_id = p_ps_rec.payment_schedule_id;
1026 
1027         END;
1028 
1029       ELSE
1030 
1031     -- As inventory item id = null, discount basis = 'F' makes no sense;
1032     -- Set discount basis = 'T'
1033 
1034 	-- Bug 8298719
1035 	IF p_disc_rec.calc_disc_on_lines <> 'L' THEN
1036 	       p_disc_rec.calc_disc_on_lines := 'T';
1037 	END IF;
1038 	l_numerator := p_ps_rec.amount_line_items_original;
1039 
1040       END IF;
1041 
1042       l_denominator := p_ps_rec.amount_due_original;
1043 
1044     ELSE -- calc_disc_on_lines IN T,Y (and I?)
1045 
1046       l_numerator := p_ps_rec.amount_line_items_original;
1047       l_denominator := p_ps_rec.amount_due_original;
1048 
1049     END IF;
1050     -- If discount basis = 'T' then get the tax amounts.
1051 
1052     IF (p_disc_rec.calc_disc_on_lines = 'T') THEN
1053 
1054       BEGIN
1055     	SELECT nvl(tax_original,0)
1056 	INTO   l_tax_original
1057 	FROM   ar_payment_schedules
1058 	WHERE  payment_schedule_id = p_ps_rec.payment_schedule_id;
1059       END;
1060     --
1061     -- Added for bug 657409.
1062        BEGIN
1063          SELECT nvl(freight_original,0)
1064          INTO   l_freight_original
1065          FROM   ar_payment_schedules
1066          WHERE  payment_schedule_id = p_ps_rec.payment_schedule_id;
1067        END;
1068 
1069         l_numerator := l_numerator + l_tax_original + l_freight_original;
1070     --
1071     END IF;
1072     --
1073     IF (l_adjustments) THEN
1074         l_numerator := l_numerator + l_line_adjusted;
1075         l_denominator := l_denominator + l_amount_adjusted;
1076     END IF;
1077     --
1078     IF (l_credit_memos) THEN
1079         l_numerator := l_numerator - l_line_applied;
1080         l_denominator := l_denominator - l_amount_applied;
1081     END IF;
1082     --
1083     IF (l_tax_adjustments) AND (p_disc_rec.calc_disc_on_lines = 'T') OR
1084        (l_tax_adjustments) AND (p_disc_rec.calc_disc_on_lines = 'F') THEN
1085         l_numerator := l_numerator + l_tax_line_adjusted;
1086     END IF;
1087     --
1088     IF (l_tax_credit_memos) AND (p_disc_rec.calc_disc_on_lines = 'T') OR
1089        (l_tax_credit_memos) AND (p_disc_rec.calc_disc_on_lines = 'F')  THEN
1090         l_numerator := l_numerator - l_tax_line_applied;
1091     END IF;
1092     --
1093     p_disc_rec.adjusted_ado := l_denominator;
1094 
1095     -- Bug 592696 if amount due original is 0 then discount is 0
1096     -- prevent division by 0.
1097 
1098     IF l_denominator = 0 THEN
1099        l_multiplier := 0;
1100     ELSE
1101        l_multiplier := l_numerator / l_denominator;
1102     END IF;
1103 
1104     IF PG_DEBUG in ('Y', 'C') THEN
1105        arp_standard.debug(   '  l_multiplier:'||TO_CHAR(l_multiplier));
1106     END IF;
1107     p_disc_rec.earned_disc_pct := p_disc_rec.earned_disc_pct * l_multiplier;
1108     p_disc_rec.best_disc_pct :=  p_disc_rec.best_disc_pct * l_multiplier;
1109     --
1110     IF PG_DEBUG in ('Y', 'C') THEN
1111        arp_standard.debug(   '  p_disc_rec.adjusted_ado:'||TO_CHAR(p_disc_rec.adjusted_ado));
1112        arp_standard.debug(   '  p_disc_rec.earned_disc_pct:'||TO_CHAR(p_disc_rec.earned_disc_pct));
1113        arp_standard.debug(   '  p_disc_rec.best_disc_pct:'||TO_CHAR(p_disc_rec.best_disc_pct));
1114        arp_standard.debug( 'arp_calculate_discount.correct_lines_only_discounts() -' );
1115     END IF;
1116     --
1117     EXCEPTION
1118         WHEN OTHERS THEN
1119            IF PG_DEBUG in ('Y', 'C') THEN
1120               arp_standard.debug( 'Exception: arp_calculate_discount.correct_lines_only_discounts()' );
1121            END IF;
1122            RAISE;
1123 END correct_lines_only_discounts;
1124 --
1125 /*===========================================================================+
1126  | PROCEDURE                                                                 |
1127  |    decrease_discounts_to_adr                                              |
1128  |                                                                           |
1129  | DESCRIPTION                                                               |
1130  |    Decrease Discounts so ADR(Amount Due Remaining) is not exceeded.       |
1131  |                                                                           |
1132  | SCOPE - PRIVATE                                                           |
1133  |                                                                           |
1134  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
1135  |                                                                           |
1136  | ARGUMENTS  : IN:                                                          |
1137  |                      p_ps_rec - Payment Schedule Record  |
1141  |                      p_earned_discount - Earned Discount                  |
1138  |                                                                           |
1139  |              IN OUT:                                                      |
1140  |                      p_disc_rec - Discount Record                  |
1142  |                      p_unearned_discount - Unearned Discount              |
1143  |                                                                           |
1144  |              OUT:                                                         |
1145  |                                                                           |
1146  | RETURNS    : NONE                                                         |
1147  |                                                                           |
1148  |                                                                           |
1149  | NOTES                                                                     |
1150  |                                                                           |
1151  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
1152  |                                                                           |
1153  +===========================================================================*/
1154 PROCEDURE decrease_discounts_to_adr(
1155     p_disc_rec IN OUT NOCOPY discount_record_type,
1156     p_ps_rec IN ar_payment_schedules%ROWTYPE,
1157     p_earned_disc IN OUT NOCOPY NUMBER,
1158     p_unearned_disc IN OUT NOCOPY NUMBER) IS
1159     l_amt_due_remaining NUMBER;
1160     l_amt NUMBER;
1161     l_new_amt_due_remaining NUMBER;
1162 BEGIN
1163     IF PG_DEBUG in ('Y', 'C') THEN
1164        arp_standard.debug( 'arp_calculate_discount.decrease_discounts_to_adr() +' );
1165     END IF;
1166     --
1167     l_amt_due_remaining := p_ps_rec.amount_due_remaining;
1168     l_amt := p_disc_rec.input_amt;
1169     -- Subtract payment amount from ADR.
1170     l_new_amt_due_remaining := l_amt_due_remaining -
1171                           l_amt;
1172     -- If the input amount exceeded the input ADR, then the sign
1173     -- of the difference will not be the same as the input ADR. If
1174     -- this is the case, set discounts to zero and exit.
1175     IF ( ( l_amt_due_remaining > 0 AND l_new_amt_due_remaining < 0 ) OR (l_amt_due_remaining < 0 AND l_new_amt_due_remaining > 0)) THEN
1176     	 p_earned_disc := 0;
1177     	 p_unearned_disc := 0;
1178         RETURN;
1179     END IF;
1180     --
1181     --If taking the full earned discount will overpay the payment
1182     --schedule, set earned discount = remaining amount, set unearned
1183     --discount to zero, and exit.
1184     IF ( ( l_amt_due_remaining > 0 AND p_earned_disc > l_new_amt_due_remaining ) OR ( l_amt_due_remaining < 0 AND p_earned_disc < l_new_amt_due_remaining ) ) THEN
1185          p_earned_disc := l_new_amt_due_remaining ;
1186          p_unearned_disc := 0;
1187     RETURN;
1188     END IF;
1189     --
1190     -- Subtract earned discount from ADR.
1191     l_new_amt_due_remaining := l_new_amt_due_remaining - p_earned_disc;
1192     -- If taking the full unearned discount will overpay the payment
1193     -- schedule, set unearned discount = remaining amount.
1194     IF ( ( l_amt_due_remaining > 0 AND p_unearned_disc > l_new_amt_due_remaining ) OR ( l_amt_due_remaining < 0 AND p_unearned_disc < l_new_amt_due_remaining ) )  THEN
1195 --         p_unearned_disc := l_amt_due_remaining;
1196          p_unearned_disc := l_new_amt_due_remaining;
1197         RETURN;
1198     END IF;
1199     --
1200     IF PG_DEBUG in ('Y', 'C') THEN
1201        arp_standard.debug( 'arp_calculate_discount.decrease_discounts_to_adr() +' );
1202     END IF;
1203     --
1204     EXCEPTION
1205         WHEN OTHERS THEN
1206            IF PG_DEBUG in ('Y', 'C') THEN
1207               arp_standard.debug( 'Exception: arp_calculate_discount.decrease_discounts_to_adr()');
1208            END IF;
1209            RAISE;
1210 END decrease_discounts_to_adr;
1211 --
1212 /*===========================================================================+
1213  | PROCEDURE                                                                 |
1214  |    determine_max_allowed_disc                                             |
1215  |                                                                           |
1216  | DESCRIPTION                                                               |
1217  |    Determine Maximum Allowable Discount                                   |
1218  |                                                                           |
1219  | SCOPE - PRIVATE                                                           |
1220  |                                                                           |
1221  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
1222  |                                                                           |
1223  | ARGUMENTS  : IN:                                                          |
1224  |                      p_mode,  p_ps_rec - Payment Schedule Record  |
1225  |                                                                           |
1226  |              IN OUT:                                                      |
1227  |                      p_disc_rec - Discount Record                  |
1228  |                                                                           |
1229  |              OUT:                                                         |
1230  |                                                                           |
1231  | RETURNS    : NONE                                                         |
1232  |                                                                           |
1236  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
1233  |                                                                           |
1234  | NOTES                                                                     |
1235  |                                                                           |
1237  |                                                                           |
1238  +===========================================================================*/
1239 PROCEDURE determine_max_allowed_disc(
1240     p_mode IN NUMBER,
1241     p_disc_rec IN OUT NOCOPY arp_calculate_discount.discount_record_type,
1242     p_ps_rec IN ar_payment_schedules%ROWTYPE ) IS
1243     l_amount_adjusted NUMBER;
1244     l_amount_applied NUMBER;
1245     l_adjustments BOOLEAN;
1246     l_credit_memos BOOLEAN;
1247     l_max_allowed_discount NUMBER;
1248     l_amt_due_original NUMBER;
1249 BEGIN
1250     IF PG_DEBUG in ('Y', 'C') THEN
1251        arp_standard.debug( 'arp_calculate_discount.determine_max_allowed_disc() +' );
1252     END IF;
1253     --
1254     l_adjustments := TRUE;
1255     l_credit_memos := TRUE;
1256     --
1257     --Get adjusted ADO. This is ADO + sum(AMOUNT_ADJUSTED) -
1258     -- sum(RA CREDITED). If calc_disc_on_lines = 'Y', then this
1259     -- value has already been computed and stored in adjusted_ado
1260     -- of the disc_struct record type. Otherwise, select from the
1261     -- database.
1262     IF ( p_disc_rec.adjusted_ado IS NULL ) THEN
1263     --  /*=========================================+
1264     --    Need to select and calculate adjusted ADO
1265     --   +=========================================*/
1266         IF PG_DEBUG in ('Y', 'C') THEN
1267            arp_standard.debug(  'Selecting from database ' );
1268         END IF;
1269         BEGIN
1270               SELECT sum(amount)
1271               INTO l_amount_adjusted
1272               FROM AR_ADJUSTMENTS
1273               WHERE payment_schedule_id = p_ps_rec.payment_schedule_id
1274               AND status = 'A';
1275         END;
1276         --
1277         IF ( l_amount_adjusted IS NULL ) THEN
1278             IF PG_DEBUG in ('Y', 'C') THEN
1279                arp_standard.debug(  'No adjustments for payment schedule' );
1280             END IF;
1281             l_adjustments := FALSE;
1282         END IF;
1283         --
1284         BEGIN
1285             SELECT sum(amount_applied)
1286             INTO l_amount_applied
1287             FROM AR_RECEIVABLE_APPLICATIONS
1288             WHERE application_type = 'CM'
1289             AND applied_payment_schedule_id = p_ps_rec.payment_schedule_id
1290             AND status = 'APP'
1291             AND application_rule in ('65','66','67');
1292         END;
1293         --
1294         IF ( l_amount_applied IS NULL ) THEN
1295             IF PG_DEBUG in ('Y', 'C') THEN
1296                arp_standard.debug(  'No credit memos for payment schedule' );
1297             END IF;
1298             l_credit_memos := FALSE;
1299         END IF;
1300         --
1301         l_amt_due_original := p_ps_rec.amount_due_original;
1302     ---
1303     ---
1304         IF (l_adjustments) THEN
1305             l_amt_due_original := l_amt_due_original + l_amount_adjusted;
1306         END IF;
1307         --
1308         IF (l_credit_memos) THEN
1309            l_amt_due_original := l_amt_due_original - l_amount_applied;
1310         END IF;
1311         --
1312         IF ( NOT l_adjustments AND NOT l_credit_memos) THEN
1313            p_disc_rec.adjusted_ado := p_ps_rec.amount_due_original;
1314         ELSE
1315            p_disc_rec.adjusted_ado := l_amt_due_original;
1316         END IF;
1317         --
1318 ---
1319 ---
1320     ELSE
1321     --  =========================================+
1322     --    Adjusted ADO already stored.
1323     --  =========================================
1324         l_amt_due_original := p_disc_rec.adjusted_ado;
1325     END IF;
1326 ---
1327 ---
1328     --
1329     -- Get max allowed total discount.
1330     -- multiply best percentage by adjusted ADO  to get max total discount
1331     IF (p_mode = AR_DIRECT_NEW_DISC OR p_mode = AR_DEFAULT_NEW_DISC) THEN
1332         IF PG_DEBUG in ('Y', 'C') THEN
1333            arp_standard.debug(   'Default or Direct Mode p_mode=' || to_char(p_mode));
1334         END IF;
1335         l_max_allowed_discount :=  p_disc_rec.best_disc_pct *
1336                                    p_disc_rec.adjusted_ado;
1337                             -- Modified for RT Bug Feb 28, 97.
1338                                    -- p_ps_rec.amount_due_original;
1339     ELSE
1340         IF PG_DEBUG in ('Y', 'C') THEN
1341            arp_standard.debug(   'Not in Default/Direct Mode p_mode=' || to_char(p_mode));
1342         END IF;
1343         l_max_allowed_discount :=  p_disc_rec.best_disc_pct *
1344                                    l_amt_due_original;
1345     END IF;
1346     --
1347     -- Added Logic for Rounding Nov 12, 96:  Bug #408762
1348     --
1349        l_max_allowed_discount :=
1350           arpcurr.CurrRound(l_max_allowed_discount,  p_ps_rec.invoice_currency_code);
1351     --
1352     --
1353     -- Subtract discounts already taken from max total discount.
1354     l_max_allowed_discount := l_max_allowed_discount -
1355                               p_ps_rec.discount_taken_earned -
1356                               p_ps_rec.discount_taken_unearned;
1357     --
1361     -- BUG 3497682
1358     -- If the discount taken exceeds the max total discount,set
1359     --   max allowable discount to zero and exit.
1360     --
1362     IF ( (l_max_allowed_discount < 0 and l_amt_due_original > 0) or
1363          (l_max_allowed_discount > 0 and l_amt_due_original < 0 )) THEN
1364         p_disc_rec.max_disc := 0;
1365         RETURN;
1366     END IF;
1367     --
1368     -- Populate max allowable discount and exit.
1369     --
1370     p_disc_rec.max_disc := l_max_allowed_discount;
1371     IF PG_DEBUG in ('Y', 'C') THEN
1372        arp_standard.debug( 'arp_calculate_discount.determine_max_allowed_disc() -' );
1373     END IF;
1374     --
1375     EXCEPTION
1376         WHEN OTHERS THEN
1377            IF PG_DEBUG in ('Y', 'C') THEN
1378               arp_standard.debug( 'Exception: arp_calculate_discount.determine_max_allowed_disc()');
1379            END IF;
1380            RAISE;
1381 END determine_max_allowed_disc;
1382 --
1383 /*===========================================================================+
1384  | PROCEDURE                                                                 |
1385  |    calculate_direct_discount                                              |
1386  |                                                                           |
1387  | DESCRIPTION                                                               |
1388  |              Calculate Direct Discount                                    |
1389  |								             |
1390  | SCOPE - PRIVATE                                                           |
1391  |                                                                           |
1392  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
1393  |                                                                           |
1394  | ARGUMENTS  : IN:                                                          |
1395  |                      p_ps_rec - Payment Schedule Record  |
1396  |                                                                           |
1397  |              IN OUT:                                                      |
1398  |                      p_disc_rec - Discount Record                  |
1399  |                      p_earned_discount - Earned Discount                  |
1400  |                      p_unearned_discount - Unearned Discount              |
1401  |                                                                           |
1402  |              OUT:                                                         |
1403  |                                                                           |
1404  | RETURNS    : NONE                                                         |
1405  |                                                                           |
1406  |                                                                           |
1407  | NOTES                                                                     |
1408  |                                                                           |
1409  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
1410  |  03/30/00   R Yeluri           Added rounding logic to calculate    |
1411  |                                earned and unearned discounts by     |
1412  |                                maintaining previous totals. Bug fix |
1413  |                                910516                               |
1414  |  04/25/02   S.Nambiar          Bug 2334691 - If the discount on partial
1415  |                                payment flag is 'Y' in system option, then
1416  |                                check the partial payment flag on payment
1417  |                                term,and take the flag from payment term. But
1418  |                                if the flag is 'N' in system option, then
1419  |                                no matter what payment term flag says,partial
1420  |                                discounts should not be allowed.
1421  |                                                                           |
1422  +===========================================================================*/
1423 PROCEDURE calculate_direct_discount(
1424     p_mode IN NUMBER,
1425     p_disc_rec IN OUT NOCOPY discount_record_type,
1426     p_ps_rec IN ar_payment_schedules%ROWTYPE,
1427     p_earned_disc IN OUT NOCOPY NUMBER,
1428     p_unearned_disc IN OUT NOCOPY NUMBER,
1429     p_called_from IN VARCHAR2 DEFAULT 'AR') IS
1430     l_ado NUMBER;
1431     l_earned_disc_pct NUMBER;
1432     l_best_pct NUMBER;
1433     l_input_amt NUMBER;
1434     l_amt_due_remaining NUMBER;
1435     l_best_disc NUMBER;
1436     l_temp NUMBER;
1437 
1438     -- Added the following variables to fix bug 910516
1439     l_amount_applied_to NUMBER;
1440     l_earned_discount_taken NUMBER ;
1441     l_unearned_discount_taken NUMBER ;
1442     l_input_amt_earned NUMBER;
1443     l_input_amt_unearned NUMBER;
1444     l_discount_remaining NUMBER ;
1445     l_sys_disc_partial_pay_flag  VARCHAR2(1) := 'N' ;
1446     l_ps_disc_partial_pay_flag  VARCHAR2(1) := 'N' ;
1447 
1448 BEGIN
1449     IF PG_DEBUG in ('Y', 'C') THEN
1450        arp_standard.debug( 'arp_calculate_discount.calculate_direct_discount() +' );
1451     END IF;
1452     --
1453     l_ado := p_disc_rec.adjusted_ado;
1454     l_earned_disc_pct := p_disc_rec.earned_disc_pct;
1455     l_best_pct := p_disc_rec.best_disc_pct;
1456     l_input_amt := p_disc_rec.input_amt;
1457     l_ps_disc_partial_pay_flag := p_disc_rec.disc_partial_pmt_flag;
1458 
1459 
1460     -- Added here by Ketul Nov 18, 96 for Bug #423908
1461     l_amt_due_remaining := p_ps_rec.amount_due_remaining;
1462     IF PG_DEBUG in ('Y', 'C') THEN
1466     END IF;
1463        arp_standard.debug(   '  l_earned_disc_pct:'||TO_CHAR(l_earned_disc_pct));
1464        arp_standard.debug(   '  l_best_pct:'||TO_CHAR(l_best_pct));
1465        arp_standard.debug(   '  l_input_amt:'||TO_CHAR(l_input_amt));
1467     --Methods for calculating discounts depend on whether or not
1468     --discounts are allowed on partial payments.
1469 
1470     -- Initialized the following to fix bug 910516
1471     l_input_amt_earned := 0;
1472     l_input_amt_unearned := 0;
1473     l_amount_applied_to := 0;
1474     l_earned_discount_taken := 0;
1475     l_unearned_discount_taken := 0;
1476 
1477     SELECT arp_standard.sysparm.partial_discount_flag
1478     INTO l_sys_disc_partial_pay_flag
1479     FROM dual;
1480 
1481    /*--------------------------------------------------------------------+
1482     |Bug 2334691 - If partial discount flag in system option is 'N' then |
1483     |l_disc_rec.disc_partial_pmt_flag= 'N' , if discount flag is 'Y' on  |
1484     |system option, then take the value from payment terms record        |
1485     *--------------------------------------------------------------------*/
1486 
1487     IF PG_DEBUG in ('Y', 'C') THEN
1488        arp_standard.debug(   'Partial Discount flag System Options = '|| l_sys_disc_partial_pay_flag);
1489        arp_standard.debug(   'Partial Discount flag Payment Term = '|| l_ps_disc_partial_pay_flag);
1490     END IF;
1491 
1492     IF NVL(l_sys_disc_partial_pay_flag,'N') = 'N' THEN
1493            l_ps_disc_partial_pay_flag := 'N';
1494     ELSE
1495            null;
1496     END IF;
1497 
1498 
1499     IF  NVL(l_ps_disc_partial_pay_flag,'N') = 'Y'
1500     THEN
1501         IF PG_DEBUG in ('Y', 'C') THEN
1502            arp_standard.debug(  '  disc_partial_pmt_flag: Y' );
1503         END IF;
1504         --
1505         --If partial payment discount is allowed then the following steps
1506         --are done.
1507         --When earned discount % = 100%, discount = ADR.
1508 
1509         -- Added by to fix bug 910516.
1510         -- This will enable to maintain running totals for amount_applied,
1511         -- earned_discount and unearned_discount, to eliminate rounding
1512         -- errors during calculation of earned and unearned discounts
1513 
1514         begin
1515 	/*For bug 2448636 to populate l_input_amt correctly
1516 	   retrieved sum(amount_applied) instead of sum(line_applied)*/
1517                 select  nvl(sum(amount_applied),0),
1518                         nvl(sum(earned_discount_taken),0),
1519                         nvl(sum(unearned_discount_taken),0)
1520                 into    l_amount_applied_to, l_earned_discount_taken,
1521                         l_unearned_discount_taken
1522                 from    ar_receivable_applications
1523                 where   applied_payment_schedule_id =
1524                                         p_ps_rec.payment_schedule_id
1525                 and     application_type = 'CASH'
1526                 and     status = 'APP';
1527 
1528           IF PG_DEBUG in ('Y', 'C') THEN
1529              arp_standard.debug(  'from ar_rec_app :');
1530              arp_standard.debug(  'payment_schedule_id = ' || to_char(p_ps_rec.payment_schedule_id));
1531              arp_standard.debug(  'l_amount_applied_to = ' || to_char(l_amount_applied_to));
1532              arp_standard.debug(  'l_earned_discount_taken = ' || to_char(l_earned_discount_taken));
1533              arp_standard.debug(  'l_unearned_discount_taken = ' || to_char(l_unearned_discount_taken));
1534           END IF;
1535         end;
1536 
1537         IF l_earned_disc_pct = 1
1538         THEN
1539             p_earned_disc := p_ps_rec.amount_due_remaining;
1540         ELSE
1541             --  calculate earned discount
1542             --  If adr - (adr)*(disc%) < payment amount, earned discount = (adr)*(disc%)
1543             --
1544 
1545             l_amt_due_remaining := p_ps_rec.amount_due_remaining;
1546             l_temp := l_amt_due_remaining
1547 	            - arpcurr.CurrRound(l_amt_due_remaining*l_earned_disc_pct,
1548 		                        p_ps_rec.invoice_currency_code);
1549 
1550             IF PG_DEBUG in ('Y', 'C') THEN
1551                arp_standard.debug(  'l_temp = ' || to_char(l_temp));
1552             END IF;
1553 
1554             IF ( ( l_amt_due_remaining > 0 AND l_temp <= l_input_amt ) OR
1555               ( l_amt_due_remaining < 0 AND l_temp >= l_input_amt ) )
1556             THEN
1557                 p_earned_disc := l_amt_due_remaining * l_earned_disc_pct;
1558             ELSE
1559                 /*-----------------------------------------------------
1560                 Bug fix 910516
1561                 Add any previous applications to the current input amt
1562                 and calculate the earned discount on the sum. Later the
1563                 correct earned discount is got by subtracting the discount
1564                 taken from the earned discount.
1565 
1566                 Bug 2598297 :
1567                 adding back previous amount applications into l_input_amt_earned
1568                 and then using this amount to compute discount based on *current*
1569                 discount rate is incorrect, because the discount rate may have
1570                 been different for previous applications.
1571 
1572                 Instead, compute discount earned for current receipt only
1573                 and then later add back all discount amounts taken
1574                 --------------------------------------------------------*/
1575 
1579 
1576                 -- replace following line :
1577                 -- l_input_amt_earned := l_input_amt + l_amount_applied_to;
1578                 -- with :
1580                 l_input_amt_earned := l_input_amt;
1581 
1582                 IF PG_DEBUG in ('Y', 'C') THEN
1583                    arp_standard.debug(
1584                                       'current receipt amount : l_input_amt_earned --:' ||
1585                                       TO_CHAR(l_input_amt_earned));
1586                 END IF;
1587 
1588                 /*------------------------------------------------------------
1589 
1590                 adr - (adr)*(disc%) >= payment amount
1591 
1592                 earned discount = (payment amount) * (discount %)
1593                                   ---------------------------------
1594                                           1 - (discount %)
1595                 --------------------------------------------------------------*/
1596 
1597                 -- discount for the current receipt application
1598                 p_earned_disc := (l_input_amt_earned * l_earned_disc_pct) /
1599                                  ( 1 - l_earned_disc_pct );
1600 
1601                 -- Bug 2716569 : took out extraneous code that was adding and then later subtracting
1602                 -- l_earned_discount_taken from p_earned_disc
1603                 -- also consolidated debug messages in one if pg_debug if block
1604 
1605                 IF PG_DEBUG in ('Y', 'C') THEN
1606                    arp_standard.debug(
1607                                       'discount available for THIS receipt : ' ||
1608                                       to_char(p_earned_disc));
1609 
1610                    arp_standard.debug('calculate_direct_discount: total redeemable discount 1 : ' ||
1611                                       TO_CHAR(p_earned_disc + l_earned_discount_taken));
1612                 END IF;
1613             END IF;
1614 
1615             IF PG_DEBUG in ('Y', 'C') THEN
1616                arp_standard.debug(   'total redeemable discount 3 :'||TO_CHAR(p_earned_disc));
1617             END IF;
1618 
1619         END IF;
1620         --
1621         -- Calculate unearned discount.
1622         -- unearned discount = ((best %) * (input amount)) - (earned
1623         -- discount)
1624         -- If current percent equals best percent, unearned discount =0.
1625         --
1626         IF l_earned_disc_pct = l_best_pct
1627         THEN
1628             p_unearned_disc := 0;
1629         ELSE
1630             -- Get best discount
1631             --
1632             -- check special case: 100% discount
1633             IF l_earned_disc_pct = 1
1634             THEN
1635                 l_best_disc := p_ps_rec.amount_due_remaining;
1636             ELSE
1637                 -- If discount is 100%, best dicount = ADR, otherwise
1638                 -- If adr - (adr)*(disc%) < payment amount, then best discount =
1639                 -- (adr)*(disc%)
1640                 --
1641                 l_temp := l_amt_due_remaining - l_amt_due_remaining*l_best_pct;
1642                 IF ( ( l_amt_due_remaining > 0 AND l_temp < l_input_amt ) OR
1643                    ( l_amt_due_remaining < 0 AND l_temp > l_input_amt ) ) THEN
1644                     l_best_disc := l_amt_due_remaining*l_best_pct;
1645                 ELSE
1646                     -- added for bugfix 910516
1647                  l_input_amt_unearned := l_input_amt + l_amount_applied_to;
1648 
1649                     -- Otherwise best discount = (payment amount * best %)
1650                     --                            -------------------------
1651                     --                             1- best %
1652                   -- Added the condition to fix bug 1236196
1653                   IF l_best_pct <> 1 THEN
1654                     l_best_disc := (l_input_amt_unearned*l_best_pct ) /
1655                                                 ( 1 - l_best_pct );
1656                   END IF;
1657             IF PG_DEBUG in ('Y', 'C') THEN
1658                arp_standard.debug(  'ptr 1- l_unearned_disc:'||TO_CHAR(l_best_disc));
1659             END IF;
1660                 l_best_disc := l_best_disc - l_unearned_discount_taken;
1661             IF PG_DEBUG in ('Y', 'C') THEN
1662                arp_standard.debug(  'ptr 2- l_unearned_disc:'||TO_CHAR(l_best_disc));
1663             END IF;
1664                 END IF;
1665             END IF;
1666             --
1667             -- Subtract earned discount from best discount to get unearned
1668             -- discount.
1669             p_unearned_disc := l_best_disc - p_earned_disc;
1670         END IF;
1671     --
1672     ELSE
1673          IF PG_DEBUG in ('Y', 'C') THEN
1674             arp_standard.debug(  '  disc_partial_pmt_flag: !Y' );
1675          END IF;
1676          -- If partial payment discount is not allowed, then the following
1677          -- steps are taken.
1678          -- earned discount = (current %) * ADO
1679          p_earned_disc := l_earned_disc_pct * l_ado;
1680          --
1681          -- and unearned discount = (best% * ADO) - (earned discount)
1682          p_unearned_disc := (l_best_pct * l_ado ) - p_earned_disc;
1683          --
1684     END IF;
1685     --
1686     -- Added Logic for Rounding Nov 12, 96:  Bug #408762
1687     --
1688        p_earned_disc :=
1689            arpcurr.CurrRound(p_earned_disc,  p_ps_rec.invoice_currency_code);
1690        p_unearned_disc :=
1691            arpcurr.CurrRound(p_unearned_disc,  p_ps_rec.invoice_currency_code);
1692     --
1696     THEN
1693     -- make sure max discount is not exceeded. reduce discounts as needed
1694     --
1695     IF NVL(l_ps_disc_partial_pay_flag,'N') = 'N'
1697         -- If (input amount + discount to take) < ADR , then
1698         -- Set discount to 0.
1699         --
1700         IF p_disc_rec.earned_both_flag = 'B'
1701         THEN
1702             l_temp := l_input_amt + p_earned_disc + p_unearned_disc;
1703         ELSE
1704             l_temp := l_input_amt + p_earned_disc;
1705         END IF;
1706         --
1707         /* bug 3497682:  */
1708 /*FP Bug 5335376 for Bug  5223829 Leftover changes of bug for case of system option partial discount unchecked
1709   Modify the check condition to include dispute amount based on parameter p_called_from*/
1710 
1711         IF p_called_from = 'OIR' THEN
1712           IF ( (l_temp < (l_amt_due_remaining + nvl(p_ps_rec.amount_in_dispute,0))and
1713                 p_ps_rec.amount_due_original >= 0) or
1714                (l_temp > (l_amt_due_remaining + nvl(p_ps_rec.amount_in_dispute,0)) and
1715                 p_ps_rec.amount_due_original < 0))
1716           THEN
1717               p_earned_disc := 0;
1718               p_unearned_disc := 0;
1719           END IF;
1720         ELSE
1721 
1722           IF ( (l_temp < l_amt_due_remaining and
1723               p_ps_rec.amount_due_original >= 0) or
1724              (l_temp > l_amt_due_remaining and
1725               p_ps_rec.amount_due_original < 0))
1726           THEN
1727             p_earned_disc := 0;
1728             p_unearned_disc := 0;
1729           END IF;
1730         END IF;
1731     END IF;
1732 
1733     IF p_mode = AR_DIRECT_NEW_DISC OR p_mode = AR_DEFAULT_NEW_DISC
1734     THEN
1735         p_unearned_disc := p_disc_rec.max_disc - p_earned_disc;
1736     END IF;
1737 
1738     IF PG_DEBUG in ('Y', 'C') THEN
1739        arp_standard.debug(   '-- p_earned_disc: '||TO_CHAR(p_earned_disc));
1740        arp_standard.debug(   '-- max_disc:' ||TO_CHAR(p_disc_rec.max_disc));
1741        arp_standard.debug(   '-- p_unearned_disc:'||TO_CHAR(p_unearned_disc));
1742        arp_standard.debug( 'arp_calculate_discount.calculate_direct_discount()-');
1743    END IF;
1744 
1745     EXCEPTION
1746         WHEN OTHERS THEN
1747            IF PG_DEBUG in ('Y', 'C') THEN
1748               arp_standard.debug(   'Exception: arp_calculate_discount.'||
1749 			'calculate_direct_discount()');
1750            END IF;
1751            RAISE;
1752 END calculate_direct_discount;
1753 --
1754 /*===========================================================================+
1755  | PROCEDURE                                                                 |
1756  |    calculate_default_discount                                             |
1757  |                                                                           |
1758  | DESCRIPTION                                                               |
1759  |              Calculate Default Discount                                   |
1760  |                                                                           |
1761  | SCOPE - PRIVATE                                                           |
1762  |                                                                           |
1763  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
1764  |                                                                           |
1765  | ARGUMENTS  : IN:                                                          |
1766  |                      p_ps_rec - Payment Schedule Record  |
1767  |                                                                           |
1768  |              IN OUT:                                                      |
1769  |                      p_disc_rec - Discount Record                  |
1770  |                      p_earned_discount - Earned Discount                  |
1771  |                      p_unearned_discount - Unearned Discount              |
1772  |                                                                           |
1773  |              OUT:                                                         |
1774  |                                                                           |
1775  | RETURNS    : NONE                                                         |
1776  |                                                                           |
1777  |                                                                           |
1778  | NOTES                                                                     |
1779  |                                                                           |
1780  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
1781  |                                                                           |
1782  +===========================================================================*/
1783 --
1784 PROCEDURE calculate_default_discount(
1785     p_mode IN NUMBER,
1786     p_disc_rec IN OUT NOCOPY discount_record_type,
1787     p_ps_rec IN ar_payment_schedules%ROWTYPE,
1788     p_earned_disc IN OUT NOCOPY NUMBER,
1789     p_unearned_disc IN OUT NOCOPY NUMBER,
1790     p_out_amt_to_apply IN OUT NOCOPY NUMBER,
1791     p_called_from IN VARCHAR2 DEFAULT 'AR') IS
1792     l_ado NUMBER;
1793     l_earned_disc_pct NUMBER;
1794     l_best_pct NUMBER;
1795     l_input_amt NUMBER;
1796     l_amt_due_remaining NUMBER;
1797     l_best_disc NUMBER;
1798     l_temp NUMBER;
1799     l_disc_to_take NUMBER;
1800     l_OIR_AR  BOOLEAN;
1801 BEGIN
1802     IF PG_DEBUG in ('Y', 'C') THEN
1806 /*FP bug 5335376 for Bug 5223829 Leftover changes of bug for case of system option partial discount unchecked
1803        arp_standard.debug( 'arp_calculate_discount.calculate_default_discount() +' );
1804     END IF;
1805     --
1807   Set variable based on parameter p_called_from*/
1808 
1809     l_OIR_AR := FALSE;
1810 
1811     l_ado := p_disc_rec.adjusted_ado;
1812     l_earned_disc_pct := p_disc_rec.earned_disc_pct;
1813     l_best_pct := p_disc_rec.best_disc_pct;
1814     l_input_amt := p_disc_rec.input_amt;
1815     l_amt_due_remaining := p_ps_rec.amount_due_remaining;
1816     --
1817     --Methods for calculating discounts depend on whether or not
1818     --discounts are allowed on partial payments.
1819     IF ( p_disc_rec.disc_partial_pmt_flag = 'Y') THEN
1820        --
1821        --If partial payment discount is allowed then the following steps
1822        --are done.
1823        --Earned discount = ADR * (earned discount %)
1824 IF PG_DEBUG in ('Y', 'C') THEN
1825    arp_standard.debug(   'l_amt_due_remaining = '||TO_CHAR( l_amt_due_remaining ));
1826    arp_standard.debug(   'l_earned_disc_pct = '||TO_CHAR( l_earned_disc_pct ));
1827 END IF;
1828        p_earned_disc := l_amt_due_remaining * l_earned_disc_pct;
1829 IF PG_DEBUG in ('Y', 'C') THEN
1830    arp_standard.debug(   'p_earned_disc = '||TO_CHAR( p_earned_disc ));
1831 END IF;
1832        --Calculate unearned discount.
1833        --If earned discount percentage equal to best discount percentage.
1834        --unearned discount = 0.
1835        IF ( l_earned_disc_pct = l_best_pct ) THEN
1836           p_unearned_disc := 0;
1837           --Otherwise
1838           --Best discount = ADR * best discount %
1839        ELSE
1840           l_best_disc := l_amt_due_remaining * l_best_pct;
1841           --Subtract earned from best to get unearned discount
1842           p_unearned_disc := l_best_disc - p_earned_disc ;
1843        END IF;
1844     ELSE
1845        --If partial payment discount is not allowed, then the following
1846        --steps are taken.
1847        --Earned discount = ADO * (earned discount %)
1848        p_earned_disc := l_ado * l_earned_disc_pct;
1849        -- calculate unearned discount
1850        --If earned discount percentage equals best discount percentage
1851        --Unearned discount = 0.
1852        IF ( l_earned_disc_pct = l_best_pct ) THEN
1853           p_unearned_disc := 0;
1854        --Otherwise
1855        --best discount = ADO * best discount%
1856        ELSE
1857           l_best_disc := l_ado * l_best_pct;
1858           --Subtract earned from best to get unearned
1859           p_unearned_disc := l_best_disc - p_earned_disc ;
1860        END IF;
1861     END IF;
1862    --
1863     -- Added logic for rounding: Nov 12, 96  Bug #408762
1864        p_earned_disc :=
1865          arpcurr.CurrRound(p_earned_disc,  p_ps_rec.invoice_currency_code);
1866        p_unearned_disc :=
1867          arpcurr.CurrRound(p_unearned_disc,  p_ps_rec.invoice_currency_code);
1868     --
1869     --
1870     -- make sure max discount is not exceeded. reduce discounts as needed
1871     IF PG_DEBUG in ('Y', 'C') THEN
1872        arp_standard.debug(   'before decrease_discounts_to_maxd, p_earned_disc = '||TO_CHAR( p_earned_disc ) );
1873        arp_standard.debug(   'before decrease_discounts_to_maxd, p_unearned_disc = '||TO_CHAR( p_unearned_disc ) );
1874        arp_standard.debug(   'before decrease_discounts_to_maxd, p_disc_rec.max_disc = '||TO_CHAR( p_disc_rec.max_disc ) );
1875     END IF;
1876 --
1877 --    arp_standard.debug( '   TEST: do not call decrease_discounts_to_maxd');
1878   decrease_discounts_to_maxd(p_disc_rec, p_ps_rec, p_earned_disc, p_unearned_disc );
1879 --
1880     IF PG_DEBUG in ('Y', 'C') THEN
1881        arp_standard.debug(   'After decrease_discounts_to_maxd, p_earned_disc = '||TO_CHAR( p_earned_disc ) );
1882        arp_standard.debug(   'After decrease_discounts_to_maxd, p_unearned_disc = '||TO_CHAR( p_unearned_disc ) );
1883        arp_standard.debug(   'After decrease_discounts_to_maxd, p_disc_rec.max_disc = '||TO_CHAR( p_disc_rec.max_disc ) );
1884     END IF;
1885 --
1886     -- amount to apply = ADR - discount to be taken
1887     -- calculate discount to take
1888     --If earned both flag = 'Y'
1889     --discount to take = earned discount + unearned discount
1890     IF ( p_disc_rec.earned_both_flag = 'B') THEN
1891        l_disc_to_take := p_earned_disc + p_unearned_disc ;
1892     --Otherwise
1893     ELSE
1894        --Discount to take = Earned discount
1895        l_disc_to_take := p_earned_disc;
1896     END IF;
1897     -- subtract discount from ADR
1898     p_out_amt_to_apply := l_amt_due_remaining - l_disc_to_take;
1899 IF PG_DEBUG in ('Y', 'C') THEN
1900    arp_standard.debug(   'p_out_amt_to_apply = '||TO_CHAR( p_out_amt_to_apply ));
1901    arp_standard.debug(   'l_amt_due_remaining = '||TO_CHAR( l_amt_due_remaining ));
1902    arp_standard.debug(   'l_disc_to_take = '||TO_CHAR( l_disc_to_take ));
1903 END IF;
1904     --If Input Amount = CLOSE_INVOICE then
1905     IF ( p_disc_rec.close_invoice_flag = 'Y' ) THEN
1906        RETURN;
1907     END IF;
1908     --Exit succesfully
1909     --If Profile:Default Amount Applied = Unapplied amount of payment('PMT')
1910     --Then
1911     IF ( p_disc_rec.default_amt_app = 'PMT' ) THEN
1912         --If balance due (amount to apply) < 0
1913         --then exit, else
1914         IF ( p_out_amt_to_apply  >= 0 ) THEN
1915 /* bug 3766518: we do not want to zero out the amounts */
1916 --           IF (l_input_amt < 0 ) THEN
1917 --              p_out_amt_to_apply := 0;
1921 /*FP bug 5335376 for Bug 5223829 Leftover changes of bug for case of system option partial discount unchecked
1918 --              p_earned_disc := 0;
1919 --              p_unearned_disc := 0;
1920 --           ELSE
1922   Set variable based on  parameter p_called_from and conditional check as per discount calc*/
1923               IF p_called_from = 'OIR' then
1924                 IF ( l_input_amt < (p_out_amt_to_apply + nvl(p_ps_rec.amount_in_dispute,0))) THEN
1925                    l_OIR_AR := TRUE;
1926                 END IF;
1927               ELSE
1928                 IF ( l_input_amt < p_out_amt_to_apply ) THEN
1929                    l_OIR_AR := TRUE;
1930                 END IF;
1931               END IF;
1932 
1933              IF l_OIR_AR THEN
1934                    p_out_amt_to_apply := l_input_amt;
1935                    IF PG_DEBUG in ('Y', 'C') THEN
1936                       arp_standard.debug(   'p_out_amt_to_apply = '||TO_CHAR( p_out_amt_to_apply ));
1937                    END IF;
1938 
1939                 IF ( p_disc_rec.disc_partial_pmt_flag = 'N' ) THEN
1940                     p_earned_disc := 0;
1941                     p_unearned_disc := 0;
1942                 ELSE
1943 /*FP bug 5335376 for Bug 5223829 Call based on the parameter p_called_from*/
1944                     calculate_direct_discount( p_mode, p_disc_rec, p_ps_rec,
1945                          p_earned_disc, p_unearned_disc,p_called_from );
1946                     /*FP Bug- 5741063 Base Bug 5386459 Call procedure to reduce default discount to max availabel discount*/
1947                     decrease_discounts_to_maxd(p_disc_rec, p_ps_rec, p_earned_disc, p_unearned_disc );
1948                 END IF;
1949               END IF;
1950 --           END IF;
1951         ELSE     /* BUG 3497682: p_amt_to_apply is negative */
1952 /* bug 3766518: we do not want to zero out the amounts */
1953 --            IF (l_input_amt > 0)  then
1954 --               p_out_amt_to_apply := 0;
1955 --               p_earned_disc := 0;
1956 --               p_unearned_disc := 0;
1957 --            ELSE
1958                if (l_input_amt > p_out_amt_to_apply) then
1959                   p_out_amt_to_apply := l_input_amt;
1960                   IF ( p_disc_rec.disc_partial_pmt_flag = 'N' ) THEN
1961                     p_earned_disc := 0;
1962                     p_unearned_disc := 0;
1963                    ELSE
1964 /*FP 5335376for Bug 5223829 Call based on the parameter p_called_from*/
1965                      calculate_direct_discount( p_mode, p_disc_rec, p_ps_rec,
1966                          p_earned_disc, p_unearned_disc,p_called_from );
1967                    /*FP Bug 5741063 Base Bug 5386459 Call procedure to reduce default discount to max availabel discount*/
1968                     decrease_discounts_to_maxd(p_disc_rec, p_ps_rec, p_earned_disc, p_unearned_disc );
1969                    END IF;
1970                end if;
1971             END IF;
1972 --        END IF;
1973     END IF;
1974     --
1975     --
1976     --
1977     IF (p_mode = AR_DIRECT_NEW_DISC OR p_mode = AR_DEFAULT_NEW_DISC) THEN
1978         p_unearned_disc := p_disc_rec.max_disc - p_earned_disc;
1979     END IF;
1980     IF PG_DEBUG in ('Y', 'C') THEN
1981        arp_standard.debug( 'p_earned_disc in calculate_default_discount = '||
1982                         TO_CHAR( p_earned_disc ) );
1983        arp_standard.debug( 'max_disc in calculate_default_discount = '||
1984                         TO_CHAR( p_disc_rec.max_disc ) );
1985        arp_standard.debug( 'p_unearned_disc in calculate_default_discount = '||
1986                         TO_CHAR( p_unearned_disc ) );
1987     END IF;
1988     --
1989     --
1990     --
1991 IF PG_DEBUG in ('Y', 'C') THEN
1992    arp_standard.debug(   'p_earned_disc = '||TO_CHAR( p_earned_disc ));
1993    arp_standard.debug(   'p_out_amt_to_apply = '||TO_CHAR( p_out_amt_to_apply ));
1994 END IF;
1995     --If receipt unapplied (input amount) < 0
1996     --then Amount to default(amount to apply) =0.
1997     --else
1998     --If receipt unapplied(input amount) >= balance due(amount to apply)
1999     --exit
2000     --else
2001     --If discounts on partial payments allowed
2002     --then
2003     --call ardcdir to calculate discount
2004     --else
2005     --set discount to 0.
2006     --
2007     IF PG_DEBUG in ('Y', 'C') THEN
2008        arp_standard.debug( 'arp_calculate_discount.calculate_default_discount() -' );
2009     END IF;
2010     --
2011     EXCEPTION
2012         WHEN OTHERS THEN
2013            IF PG_DEBUG in ('Y', 'C') THEN
2014               arp_standard.debug( 'Exception: arp_calculate_discount.calculate_default_discount()');
2015            END IF;
2016            RAISE;
2017 END calculate_default_discount;
2018 --
2019 /*===========================================================================+
2020  | FUNCTION                                                                  |
2021  |    check_input                                                            |
2022  |                                                                           |
2023  | DESCRIPTION                                                               |
2024  |    Check if the all the needed fields of the discount record and the      |
2025  |    payment schedule record are populated, If not exit with error. Also    |
2026  |    the select flag is checked and if not valid then error is returned.    |
2027  |                                                                           |
2028  | SCOPE - PRIVATE                                                           |
2032  | ARGUMENTS  : IN:                                                          |
2029  |                                                                           |
2030  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
2031  |                                                                           |
2033  |                      p_disc_rec - Discount Record                         |
2034  |                      p_select_flag - Select Flag			     |
2035  | 									     |
2036  |              IN OUT:							     |
2037  |                      p_ps_rec - Payment Schedule Record                   |
2038  |                                                                           |
2039  |              OUT:                                                         |
2040  |                                                                           |
2041  | RETURNS    : TRUE / FALSE                                                 |
2042  |                                                                           |
2043  | MODIFICATION HISTORY - Created by Shiv Ragunat  - 05/25/95                |
2044  |                                                                           |
2045  |	T Schraid - 07/26/96	Modified to allow new discount bases:        |
2046  |                              'I', 'L', 'T', 'F'.  Retained original       |
2047  |                              values of 'Y' and 'N'.			     |
2048  +===========================================================================*/
2049 PROCEDURE check_input(
2050     p_disc_rec IN  discount_record_type,
2051     p_select_flag     IN BOOLEAN,
2052     p_ps_rec IN OUT NOCOPY ar_payment_schedules%ROWTYPE ) IS
2053 BEGIN
2054     IF PG_DEBUG in ('Y', 'C') THEN
2055        arp_standard.debug( 'arp_calculate_discount.check_input() +' );
2056     END IF;
2057     --
2058     -- If Input Amount equals NULL
2059     -- exit with error
2060     IF  p_disc_rec.input_amt IS NULL
2061     THEN
2062         IF PG_DEBUG in ('Y', 'C') THEN
2063            arp_standard.debug( 'arp_calculate_discount.check_input : Input amount is NULL. Must have a value.' );
2064         END IF;
2065         --error_code := AR_M_FAILURE ;
2066         IF PG_DEBUG in ('Y', 'C') THEN
2067            arp_standard.debug(   'Check input Failed' );
2068         END IF;
2069         --APP_EXCEPTION.raise_exception;
2070         RAISE ar_m_fail;
2071     END IF;
2072     -- If apply date = NULL
2073     -- exit with error
2074     IF p_disc_rec.apply_date IS NULL
2075     THEN
2076         IF PG_DEBUG in ('Y', 'C') THEN
2077            arp_standard.debug( 'arp_calculate_discount.check_input : Apply date is NULL. Must have a value.' );
2078         END IF;
2079         --error_code := AR_M_FAILURE ;
2080         IF PG_DEBUG in ('Y', 'C') THEN
2081            arp_standard.debug(   'Check input Failed' );
2082         END IF;
2083         --APP_EXCEPTION.raise_exception;
2084         RAISE ar_m_fail;
2085     END IF;
2086     -- If Select flag = FALSE
2087     -- If term_id >= 0 and term_sequence_number >=0
2088     -- If disc_partial_payment_flag <> 'Y' and <> 'N'
2089     -- Exit with error
2090     IF p_select_flag = FALSE
2091     THEN
2092         IF p_ps_rec.term_id IS NOT NULL AND p_ps_rec.terms_sequence_number IS NOT NULL
2093         THEN
2094             IF p_disc_rec.disc_partial_pmt_flag <> 'Y' AND
2095               p_disc_rec.disc_partial_pmt_flag <> 'N'
2096             THEN
2097                 IF PG_DEBUG in ('Y', 'C') THEN
2098                    arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for p_disc_rec.disc_partial_pmt_flag' );
2099                 END IF;
2100                RAISE ar_m_fail;
2101             END IF;
2102             -- If calc_disc_on_lines not in ('Y', 'N', 'I', 'L', 'T', 'F')
2103             -- Exit with error
2104             IF p_disc_rec.calc_disc_on_lines <> 'Y' AND
2105                p_disc_rec.calc_disc_on_lines <> 'N' AND
2106                p_disc_rec.calc_disc_on_lines <> 'I' AND
2107                p_disc_rec.calc_disc_on_lines <> 'L' AND
2108                p_disc_rec.calc_disc_on_lines <> 'T' AND
2109                p_disc_rec.calc_disc_on_lines <> 'F'
2110             THEN
2111                 IF PG_DEBUG in ('Y', 'C') THEN
2112                    arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for p_disc_rec.calc_disc_on_lines' );
2113                 END IF;
2114                 RAISE ar_m_fail;
2115             END IF;
2116         END IF;
2117     END IF;
2118     -- If earned_both_flag <> AR_EARNED_INDICATOR  AND <> AR_BOTH_INDICATOR
2119     -- exit with error
2120     IF ( p_disc_rec.earned_both_flag <> AR_EARNED_INDICATOR AND
2121          p_disc_rec.earned_both_flag <> AR_BOTH_INDICATOR ) THEN
2122        IF PG_DEBUG in ('Y', 'C') THEN
2123           arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for p_disc_rec.earned_both_flag' );
2124        END IF;
2125          RAISE ar_m_fail;
2126     END IF;
2127     -- If Select_flag <> TRUE AND <> FALSE
2128     -- exit with error
2129     IF ( p_select_flag <> TRUE AND p_select_flag <> FALSE ) THEN
2130         IF PG_DEBUG in ('Y', 'C') THEN
2131            arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for p_select_flag. Must be TRUE or FALSE.' );
2132         END IF;
2133          RAISE ar_m_fail;
2134     END IF;
2135     -- If payment_schedule_id <= 0
2136     -- exit with error
2137     IF ( p_ps_rec.payment_schedule_id <= 0 ) THEN
2138        IF PG_DEBUG in ('Y', 'C') THEN
2142          RAISE ar_m_fail;
2139           arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for
2140          p_ps_rec.payment_schedule_id. Must be greater than zero.' );
2141        END IF;
2143     END IF;
2144     IF p_select_flag = FALSE
2145     THEN
2146         IF ( p_ps_rec.term_id IS NULL )
2147         THEN
2148             p_ps_rec.term_id := AR_NO_TERM;
2149         ELSIF p_ps_rec.term_id < 0
2150         THEN
2151             IF PG_DEBUG in ('Y', 'C') THEN
2152                arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for p_ps_rec.term_id. Must be greater than zero. ' );
2153             END IF;
2154             RAISE ar_m_fail;
2155         END IF;
2156         IF p_ps_rec.terms_sequence_number IS NULL
2157         THEN
2158             p_ps_rec.terms_sequence_number := AR_NO_TERM;
2159         ELSIF ( p_ps_rec.terms_sequence_number < 0 )
2160         THEN
2161             IF PG_DEBUG in ('Y', 'C') THEN
2162                arp_standard.debug( 'arp_calculate_discount.check_input : Invalid value for
2163             p_ps_rec.terms_sequence_number. Must be greater than zero. ' );
2164             END IF;
2165             RAISE ar_m_fail;
2166         END IF;
2167         IF ( p_ps_rec.trx_date IS NULL ) THEN
2168             IF PG_DEBUG in ('Y', 'C') THEN
2169                arp_standard.debug( 'arp_calculate_discount.check_input : p_ps_rec.trx_date is NULL. Must have a value. ');
2170             END IF;
2171             RAISE ar_m_fail;
2172         END IF;
2173         IF ( p_ps_rec.amount_due_original IS NULL )
2174         THEN
2175             IF PG_DEBUG in ('Y', 'C') THEN
2176                arp_standard.debug( 'arp_calculate_discount.check_input : p_ps_rec.amount_due_original is NULL . Must have a value. ');
2177             END IF;
2178             RAISE ar_m_fail;
2179         END IF;
2180         IF ( p_ps_rec.invoice_currency_code IS NULL ) THEN
2181             IF PG_DEBUG in ('Y', 'C') THEN
2182                arp_standard.debug( 'arp_calculate_discount.check_input : p_ps_rec.invoice_currency_code is NULL . Must have a value. ');
2183             END IF;
2184             RAISE ar_m_fail;
2185         END IF;
2186         IF ( p_ps_rec.discount_taken_earned IS NULL ) THEN
2187             p_ps_rec.discount_taken_earned := 0;
2188         END IF;
2189         IF ( p_ps_rec.discount_taken_unearned IS NULL ) THEN
2190              p_ps_rec.discount_taken_unearned := 0;
2191         END IF;
2192         IF ( p_ps_rec.amount_line_items_original IS NULL ) THEN
2193              p_ps_rec.amount_line_items_original := 0;
2194         END IF;
2195     END IF;
2196     -- else
2197     -- If Select_flag = False
2198     -- If term_id = NULL
2199     -- term_id = AR_NO_TERM
2200     -- else
2201     -- If term_id <= 0
2202     -- exit with error
2203     -- If term_sequence_number = NULL
2204     -- term_sequence_number = AR_NO_TERM
2205     -- else
2206     -- If term_sequence_number <= 0
2207     -- exit with error
2208     -- If trx_date = NULL
2209     -- exit with error
2210     -- If amount_due_original = NULL
2211     -- exit with error
2212     -- else
2213     -- If amount_due_remaining = NULL
2214     -- exit with error
2215     -- else
2216     -- If invoice_currency_code = NULL
2217     -- exit with error
2218     -- else
2219     -- If disc_earned = NULL
2220     -- Set discount earned = 0
2221     -- If disc_unearned = NULL
2222     -- Set disc_unearned = 0
2223     -- If lines_original = NULL
2224     -- Set lines_original = 0
2225     --
2226     IF PG_DEBUG in ('Y', 'C') THEN
2227        arp_standard.debug( 'arp_calculate_discount.check_input() -' );
2228     END IF;
2229     --
2230     EXCEPTION
2231         WHEN OTHERS THEN
2232            IF PG_DEBUG in ('Y', 'C') THEN
2233               arp_standard.debug( 'Exception: arp_calculate_discount.check_input()' );
2234            END IF;
2235            RAISE;
2236 END check_input;
2237 --
2238 /*===========================================================================+
2239  | PROCEDURE                                                                 |
2240  |    decrease_discounts_to_maxd                                             |
2241  |                                                                           |
2242  | DESCRIPTION                                                               |
2243  |    Decrease Discounts so that maximum discounts not exceeded.             |
2244  |                                                                           |
2245  | SCOPE - PRIVATE                                                           |
2246  |                                                                           |
2247  | EXTERNAL  PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
2248  |                                                                           |
2249  | ARGUMENTS  : IN:                                                          |
2250  |                      p_ps_rec - Payment Schedule Record  |
2251  |                                                                           |
2252  |              IN OUT:                                                      |
2253  |                      p_disc_rec - Discount Record                  |
2254  |                      p_earned_discount - Earned Discount                  |
2255  |   			p_unearned_discount - Unearned Discount              |
2256  |  									     |
2257  |              OUT:                                                         |
2261  |                                                                           |
2258  |                                                                           |
2259  | RETURNS    : NONE                                                         |
2260  |                                                                           |
2262  | NOTES                                                                     |
2263  |                                                                           |
2264  | MODIFICATION HISTORY - Created by Shiv Ragunat - 05/24/95                 |
2265  |	jbeckett	06-JUL-2004	Bug 3527600: changes to allow for    |
2266  |					negative discounts.                  |
2267  |                                                                           |
2268  +===========================================================================*/
2269 --
2270 PROCEDURE decrease_discounts_to_maxd(
2271     p_disc_rec IN OUT NOCOPY discount_record_type,
2272     p_ps_rec IN ar_payment_schedules%ROWTYPE,
2273     p_earned_disc IN OUT NOCOPY NUMBER,
2274     p_unearned_disc IN OUT NOCOPY NUMBER) IS
2275     l_max_disc NUMBER;
2276 BEGIN
2277     IF PG_DEBUG in ('Y', 'C') THEN
2278        arp_standard.debug( 'arp_calculate_discount.decrease_discounts_to_maxd() +' );
2279     END IF;
2280 --
2281     IF ( ABS(p_disc_rec.max_disc) < ABS(p_earned_disc) ) THEN
2282 	p_earned_disc := p_disc_rec.max_disc;
2283 	p_unearned_disc := 0;
2284     ELSE
2285        l_max_disc := p_disc_rec.max_disc - p_earned_disc;
2286        IF ( ABS(l_max_disc) < ABS(p_unearned_disc) ) THEN
2287             p_unearned_disc := l_max_disc;
2288        END IF;
2289     END IF;
2290     -- If  max_disc < out_earned_disc
2291     -- set earned_discount = max_disc and unearned_disc = 0
2292     -- else
2293     -- If max-earned < full unearned discount
2294     -- set unearned discount = max-earned
2295     --
2296     IF PG_DEBUG in ('Y', 'C') THEN
2297        arp_standard.debug( 'arp_calculate_discount.decrease_discounts_to_maxd() -' );
2298     END IF;
2299     --
2300     EXCEPTION
2301         WHEN OTHERS THEN
2302            IF PG_DEBUG in ('Y', 'C') THEN
2303               arp_standard.debug( 'Exception: arp_calculate_discount.decrease_discounts_to_maxd()');
2304            END IF;
2305            RAISE;
2306 END decrease_discounts_to_maxd;
2307 --
2308 /*===========================================================================+
2309  | PROCEDURE                                                                 |
2310  | discounts_cover  - Validate args, init variables and call actual discounts|
2311  |                    procedure                                              |
2312  |                                                                           |
2313  | DESCRIPTION                                                               |
2314  |    This function validates args, init variables and calls actual discounts|
2315  |    procedure                                                              |
2316  |                                                                           |
2317  | SCOPE - PUBLIC                                                            |
2318  |                                                                           |
2319  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
2320  |      ARP_CALCULATE_DISCOUNT.calculate_discounts                           |
2321  |                                                                           |
2322  | ARGUMENTS  : IN:                                                          |
2323  |              OUT:                                                         |
2324  |                                                                           |
2325  | RETURNS    : NONE                                                         |
2326  |                                                                           |
2327  | NOTES -                                                                   |
2328  |                                                                           |
2329  | MODIFICATION HISTORY -  08/10/95 - Created by Ganesh Vaidee               |
2330  |  26-Feb-1999    Debbie Jancis     Added cash_receipt_id to arguments as   |
2331  |                                   per cpg bug 627518.                     |
2332  +===========================================================================*/
2333 PROCEDURE discounts_cover(
2334      p_mode          IN VARCHAR2,
2335      p_invoice_currency_code IN ar_cash_receipts.currency_code%TYPE,
2336      p_ps_id IN ar_payment_schedules.payment_schedule_id%TYPE,
2337      p_term_id IN ra_terms.term_id%TYPE,
2338      p_terms_sequence_number IN ar_payment_schedules.terms_sequence_number%TYPE,
2339      p_trx_date IN ar_payment_schedules.trx_date%TYPE,
2340      p_apply_date IN ar_cash_receipts.receipt_date%TYPE,
2341      p_grace_days IN NUMBER,
2342      p_default_amt_apply_flag  IN VARCHAR2,
2343      p_partial_discount_flag IN VARCHAR2,
2344      p_calc_discount_on_lines_flag IN VARCHAR2,
2345      p_allow_overapp_flag IN VARCHAR2,
2346      p_close_invoice_flag IN VARCHAR2,
2347      p_earned_disc_pct IN OUT NOCOPY
2348                           ar_payment_schedules.amount_due_original%TYPE,
2349      p_best_disc_pct IN OUT NOCOPY
2350                           ar_payment_schedules.amount_due_original%TYPE,
2351      p_input_amount   IN ar_payment_schedules.amount_due_original%TYPE,
2352      p_amount_due_original IN ar_payment_schedules.amount_due_original%TYPE,
2353      p_amount_due_remaining IN ar_payment_schedules.amount_due_remaining%TYPE,
2354      p_discount_taken_earned IN ar_payment_schedules.amount_due_original%TYPE,
2355      p_discount_taken_unearned IN
2359      p_out_discount_date    IN OUT NOCOPY DATE,
2356                           ar_payment_schedules.amount_due_original%TYPE,
2357      p_amount_line_items_original IN
2358                           ar_payment_schedules.amount_line_items_original%TYPE,
2360      p_out_earned_discount  IN OUT NOCOPY
2361                           ar_payment_schedules.amount_due_original%TYPE,
2362      p_out_unearned_discount  IN OUT NOCOPY
2363                           ar_payment_schedules.amount_due_original%TYPE,
2364      p_out_amount_to_apply  IN OUT NOCOPY
2365                           ar_payment_schedules.amount_due_original%TYPE,
2366      p_out_discount_to_take  IN OUT NOCOPY
2367                           ar_payment_schedules.amount_due_original%TYPE,
2368      p_module_name  IN VARCHAR2,
2369      p_module_version IN VARCHAR2,
2370      p_cash_receipt_id IN NUMBER  ,
2371      p_allow_discount IN VARCHAR2 DEFAULT 'Y' ) IS  /* Bug fix 3450317 */
2372 --
2373 l_use_max_cash_flag    CHAR := 'Y';
2374 l_earned_both_flag     CHAR := 'E';
2375 l_select_flag          CHAR := 'N';
2376 --
2377 l_error_code           NUMBER;
2378 l_close_invoice_flag   VARCHAR2(10);
2379 --
2380 BEGIN
2381     IF PG_DEBUG in ('Y', 'C') THEN
2382        arp_standard.debug( 'arp_calculate_discount.discounts_cover()+' );
2383     END IF;
2384   -- ARTA changes calls TA discount cover for TA installation
2385   IF nvl(arp_global.sysparam.ta_installed_flag,'N') = 'Y' THEN
2386      NULL; -- Do Nothing;
2387      -- Removed ARTA logic for Bug 4936298
2388   ELSE
2389     IF PG_DEBUG in ('Y', 'C') THEN
2390        arp_standard.debug('discounts_cover: ' ||  'Mode              : '||p_mode );
2391        arp_standard.debug('discounts_cover: ' ||  'Currency Code     : '||p_invoice_currency_code );
2392        arp_standard.debug('discounts_cover: ' ||  'PS ID             : '||p_ps_id );
2393        arp_standard.debug('discounts_cover: ' ||  'Term Id           : '||p_term_id );
2394        arp_standard.debug('discounts_cover: ' ||  'Term Seq Num      : '||p_terms_sequence_number );
2395        arp_standard.debug('discounts_cover: ' ||  'Trx Date          : '||TO_CHAR( p_trx_date ) );
2396        arp_standard.debug('discounts_cover: ' ||  'Receipt Date      : '||TO_CHAR( p_trx_date ) );
2397        arp_standard.debug('discounts_cover: ' ||  'Grace Days        : '||p_grace_days );
2398        arp_standard.debug('discounts_cover: ' ||  'Part. Disc. Flag  : '||p_partial_discount_flag );
2399        arp_standard.debug('discounts_cover: ' ||  'Calc. Disc. Lines : '||p_calc_discount_on_lines_flag );
2400        arp_standard.debug('discounts_cover: ' ||  'Earned Disc. Pct  : '||p_earned_disc_pct );
2401        arp_standard.debug('discounts_cover: ' ||  'Best Disc. Pct    : '||p_best_disc_pct );
2402        arp_standard.debug('discounts_cover: ' ||  'Input Amount      : '||p_input_amount );
2403        arp_standard.debug('discounts_cover: ' ||  'ADO               : '||p_amount_due_original );
2404        arp_standard.debug('discounts_cover: ' ||  'ADR               : '||p_amount_due_remaining );
2405        arp_standard.debug('discounts_cover: ' ||  'Disc. Taken Earned: '||p_discount_taken_earned );
2406        arp_standard.debug('discounts_cover: ' ||  'Disc. Taken Unearn: '||p_discount_taken_unearned );
2407        arp_standard.debug('discounts_cover: ' ||  'Lines Items Orig. : '||p_amount_line_items_original );
2408        arp_standard.debug('discounts_cover: ' ||  'Out Discount Date : '||TO_CHAR( p_out_discount_date ) );
2409     END IF;
2410     --
2411     IF ( p_module_name IS NOT NULL AND p_module_version IS NOT NULL ) THEN
2412          validate_args_discounts_cover( p_mode, p_invoice_currency_code,
2413                                        p_ps_id, p_trx_date, p_apply_date );
2414     END IF;
2415     --
2416     l_close_invoice_flag := p_close_invoice_flag;
2417     --
2418     -- If TERM_ID or SEQUENCE_NUM then outputs to zeros
2419     --
2420     IF ( p_term_id IS NULL OR p_terms_sequence_number IS NULL OR p_allow_discount = 'N' ) THEN /* Bug fix 3450317 */
2421         p_earned_disc_pct := 0;
2422         p_best_disc_pct := 0;
2423         p_out_earned_discount := 0;
2424         p_out_unearned_discount := 0;
2425         p_out_discount_to_take := 0; /* Bug fix 3450317 */
2426         --
2427         -- Set Output amount to apply
2428         -- In DEFAULT mode, set amount to apply to the lesser of the
2429         -- input amount and the amount due remaining. If input is
2430         -- CLOSE_INVOICE, then use amount due remaining
2431         --
2432         -- AR_DEFAULT_DISC
2433         IF ( p_mode = AR_DEFAULT_DISC OR p_mode = AR_DEFAULT_NEW_DISC) THEN
2434             IF ( l_close_invoice_flag = 'Y' ) THEN
2435                 p_out_amount_to_apply := p_amount_due_remaining;
2436             ELSE
2437                 IF ( p_default_amt_apply_flag <> 'PMT' ) THEN
2438                              p_out_amount_to_apply := p_amount_due_remaining;
2439                 ELSE  /** ADR <  0 ***/
2440                     IF ( p_amount_due_remaining < 0 ) THEN
2441                         p_out_amount_to_apply := p_amount_due_remaining;
2442                     ELSE  /*** ADR >= 0 ***/
2443                         IF ( p_input_amount < 0 ) THEN /* input amount < 0 */
2444                             p_out_amount_to_apply := 0;
2445                         ELSE /* IF ADR < input amount */
2446                             IF ( p_amount_due_remaining < p_input_amount ) THEN
2447                                 p_out_amount_to_apply :=
2448                                              NVL( p_amount_due_remaining, 0 );
2449                             ELSE /* ADR >= inout amount */
2450                                 p_out_amount_to_apply :=
2454                     END IF; /* ADR <  0 ***/
2451                                              NVL( p_input_amount, 0 );
2452                             END IF; /* /* IF ADR < input amount */
2453                         END IF; /* input amount < 0 */
2455                 END IF; /** p_default_amt_apply_flag <> 'PMT' */
2456             END IF; /* l_close_invoice_flag = 'Y' */
2457         END IF;  /*  p_mode = 1 */
2458         --
2459         RETURN;
2460     END IF; /* p_term_id IS NULL OR p_terms_sequence_number IS NULL */
2461     --
2462     -- If mode is DIRECT and Over app flag is 'Y' then max cash flag is FALSE
2463     --
2464     IF ( p_mode = AR_DIRECT_DISC OR p_mode = AR_DIRECT_NEW_DISC ) THEN /* DIRECT   */
2465         IF ( p_allow_overapp_flag = 'Y' ) THEN
2466             l_use_max_cash_flag := 'N';
2467         ELSE
2468             l_use_max_cash_flag := 'Y';
2469         END IF;
2470     --
2471     -- If profile option 'Default Amount Applied' is 'Remaining amt of inv',
2472     -- close invoice flag is 'Y'
2473     ELSE /* DEFAULT MODE */
2474         IF ( p_default_amt_apply_flag <> 'PMT' ) THEN
2475             l_close_invoice_flag := 'Y';
2476         END IF;
2477     END IF;
2478     --
2479     -- set earned_both_flag to BOTH if discounts not allowed on partial
2480     -- payments. This is because discount package would return 0 discounts if
2481     -- earned discount alone is insufficient to close the payment schedule.
2482     -- We want to return a default (OUT_DISC_TO_TAKE) of zero in that case,
2483     -- but still return earned and unearned discounts if it is possible to
2484     -- close the payment schedule using unearned discount.
2485     --
2486     IF ( p_partial_discount_flag = 'N' ) THEN
2487         l_earned_both_flag := 'B';
2488     END IF;
2489     --
2490     IF PG_DEBUG in ('Y', 'C') THEN
2491        arp_standard.debug('discounts_cover: ' ||  'arp_calculate_discount.calc_discount()-' );
2492     END IF;
2493     --
2494     arp_calculate_discount.calculate_discounts( p_input_amount,
2495                                                 p_grace_days,
2496                                                 p_apply_date,
2497                                                 p_partial_discount_flag,
2498                                                 p_calc_discount_on_lines_flag,
2499                                                 l_earned_both_flag,
2500                                                 l_use_max_cash_flag,
2501                                                 p_default_amt_apply_flag,
2502                                                 p_earned_disc_pct,
2503                                                 p_best_disc_pct,
2504                                                 p_out_earned_discount,
2505                                                 p_out_unearned_discount,
2506                                                 p_out_discount_date,
2507                                                 p_out_amount_to_apply,
2508                                                 l_close_invoice_flag,
2509                                                 p_ps_id,
2510                                                 p_term_id,
2511                                                 p_terms_sequence_number,
2512                                                 p_trx_date,
2513                                                 p_amount_due_original,
2514                                                 p_amount_due_remaining,
2515                                                 p_discount_taken_earned,
2516                                                 p_discount_taken_unearned,
2517                                                 p_amount_line_items_original,
2518                                                 p_invoice_currency_code,
2519                                                 l_select_flag,
2520                                                 p_mode,
2521                                                 l_error_code,
2522                                                 p_cash_receipt_id );
2523     --
2524     p_out_discount_to_take := p_out_earned_discount;
2525     --
2526     -- If discount is not allowed on partial payments, then
2527     -- OUT_DISC_TO_TAKE and OUT_AMT_TO_APPLY must be changed if
2528     -- unearned discount was required to close the payment schedule.
2529     --
2530     IF ( p_partial_discount_flag  = 'N' ) THEN
2531         IF ( p_out_unearned_discount <> 0 ) THEN
2532             IF ( p_mode = 0 ) THEN /* DIRECT */
2533                 p_out_discount_to_take := 0;
2534             ELSE /* DEFAULT MODE */
2535                 --
2536                 -- Add unearned discount to amount to apply
2537                 --
2538                 IF ( l_close_invoice_flag = 'N' ) THEN
2539                     p_out_amount_to_apply := p_out_amount_to_apply +
2540                                              p_out_unearned_discount;
2541                  --
2542                  -- If new amount to apply exceeds amount available,
2543                  -- set OUT_DISC_TO_TAKE = 0 and OUT_AMT_TO_APPLY = amount
2544                  -- available
2545                  --
2546                     IF ( p_out_amount_to_apply > p_input_amount ) THEN
2547                         p_out_discount_to_take := 0;
2548                         p_out_amount_to_apply := p_input_amount;
2549                     END IF;
2550                 END IF;
2551             END IF; /* DEFAULT MODE */
2552         END IF; /* unearned discount <> zero */
2553     END IF; /* discount on partial payments not allowed */
2554     --
2555   END IF;
2556     IF PG_DEBUG in ('Y', 'C') THEN
2560     EXCEPTION
2557        arp_standard.debug( 'arp_calculate_discount.discounts_cover()-' );
2558     END IF;
2559     --
2561         WHEN OTHERS THEN
2562              IF PG_DEBUG in ('Y', 'C') THEN
2563                 arp_standard.debug( 'EXCEPTION: arp_calculate_discount.discounts_cover'
2564  );
2565              END IF;
2566              RAISE;
2567 END discounts_cover;
2568 
2569 
2570 --  created an overloaded discounts_cover routine which will call the
2571 --  above procedure with a NULL for cash_receipt_id.   This was added for
2572 --  Bug 627518.    AR forms will call this function because they will not
2573 --  use Cash_receipt_id for calculating discounts.
2574 
2575 PROCEDURE discounts_cover(
2576      p_mode          IN VARCHAR2,
2577      p_invoice_currency_code IN ar_cash_receipts.currency_code%TYPE,
2578      p_ps_id IN ar_payment_schedules.payment_schedule_id%TYPE,
2579      p_term_id IN ra_terms.term_id%TYPE,
2580      p_terms_sequence_number IN ar_payment_schedules.terms_sequence_number%TYPE,
2581      p_trx_date IN ar_payment_schedules.trx_date%TYPE,
2582      p_apply_date IN ar_cash_receipts.receipt_date%TYPE,
2583      p_grace_days IN NUMBER,
2584      p_default_amt_apply_flag  IN VARCHAR2,
2585      p_partial_discount_flag IN VARCHAR2,
2586      p_calc_discount_on_lines_flag IN VARCHAR2,
2587      p_allow_overapp_flag IN VARCHAR2,
2588      p_close_invoice_flag IN VARCHAR2,
2589      p_earned_disc_pct IN OUT NOCOPY
2590                           ar_payment_schedules.amount_due_original%TYPE,
2591      p_best_disc_pct IN OUT NOCOPY
2592                           ar_payment_schedules.amount_due_original%TYPE,
2593      p_input_amount   IN ar_payment_schedules.amount_due_original%TYPE,
2594      p_amount_due_original IN ar_payment_schedules.amount_due_original%TYPE,
2595      p_amount_due_remaining IN ar_payment_schedules.amount_due_remaining%TYPE,
2596      p_discount_taken_earned IN ar_payment_schedules.amount_due_original%TYPE,
2597      p_discount_taken_unearned IN
2598                           ar_payment_schedules.amount_due_original%TYPE,
2599      p_amount_line_items_original IN
2600                           ar_payment_schedules.amount_line_items_original%TYPE,
2601      p_out_discount_date    IN OUT NOCOPY DATE,
2602      p_out_earned_discount  IN OUT NOCOPY
2603                           ar_payment_schedules.amount_due_original%TYPE,
2604      p_out_unearned_discount  IN OUT NOCOPY
2605                           ar_payment_schedules.amount_due_original%TYPE,
2606      p_out_amount_to_apply  IN OUT NOCOPY
2607                           ar_payment_schedules.amount_due_original%TYPE,
2608      p_out_discount_to_take  IN OUT NOCOPY
2609                           ar_payment_schedules.amount_due_original%TYPE,
2610      p_module_name  IN VARCHAR2,
2611      p_module_version IN VARCHAR2 ,
2612      p_allow_discount IN VARCHAR2 DEFAULT 'Y' ) IS /* Bug fix 3450317 */
2613 BEGIN
2614    -- ARTA changes calls TA discount cover for TA installation
2615   IF nvl(arp_global.sysparam.ta_installed_flag,'N') = 'Y' THEN
2616      NULL; -- Do Nothing
2617      -- Removed ARTA logic for Bug 4936298
2618   ELSE
2619      ARP_CALCULATE_DISCOUNT.discounts_cover( p_mode,
2620                                     p_invoice_currency_code,
2621                                     p_ps_id,
2622                                     p_term_id,
2623                                     p_terms_sequence_number,
2624                                     p_trx_date,
2625                                     p_apply_date,
2626                                     p_grace_days,
2627                                     p_default_amt_apply_flag,
2628                                     p_partial_discount_flag,
2629                                     p_calc_discount_on_lines_flag,
2630                                     p_allow_overapp_flag,
2631                                     p_close_invoice_flag,
2632                                     p_earned_disc_pct,
2633                                     p_best_disc_pct,
2634                                     p_input_amount,
2635                                     p_amount_due_original,
2636                                     p_amount_due_remaining,
2637                                     p_discount_taken_earned,
2638                                     p_discount_taken_unearned,
2639                                     p_amount_line_items_original,
2640                                     p_out_discount_date,
2641                                     p_out_earned_discount,
2642                                     p_out_unearned_discount,
2643                                     p_out_amount_to_apply,
2644                                     p_out_discount_to_take,
2645                                     p_module_name,
2646                                     p_module_version,
2647                                     NULL,
2648                                     p_allow_discount); /* Bug fix 3450317 */
2649   END IF;
2650 END discounts_cover;
2651 
2652 
2653 /*===========================================================================+
2654  | PROCEDURE                                                                 |
2655  |    validate_args_discounts_cover                                          |
2656  |                                                                           |
2657  | DESCRIPTION                                                               |
2658  |    Validate arguments passed to calc_discount procedure                   |
2659  |                                                                           |
2660  | SCOPE - PRIVATE                                                           |
2664  |                                                                           |
2661  |                                                                           |
2662  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED - NONE                            |
2663  |      arp_standard.debug - debug procedure                                     |
2665  | ARGUMENTS  : IN:                                                          |
2666  |                 p_mode - Mode                                             |
2667  |                 p_currrency_code - Invoice Currency Code                  |
2668  |                 p_ps_id - Payment Schedule ID                             |
2669  |                 p_term_id - Term ID                                       |
2670  |                 p_trx_date - Transaction Date                             |
2671  |                 p_apply_date - receipt date                               |
2672  |              OUT:                                                         |
2673  |                                                                           |
2674  | RETURNS    : NONE                                                         |
2675  |                                                                           |
2676  | NOTES -                                                                   |
2677  |                                                                           |
2678  | MODIFICATION HISTORY - Created by Ganesh Vaidee - 08/10/95                |
2679  |                                                                           |
2680  +===========================================================================*/
2681 PROCEDURE validate_args_discounts_cover(
2682      p_mode          IN VARCHAR2,
2683      p_invoice_currency_code IN ar_cash_receipts.currency_code%TYPE,
2684      p_ps_id IN ar_payment_schedules.payment_schedule_id%TYPE,
2685      p_trx_date IN ar_payment_schedules.trx_date%TYPE,
2686      p_apply_date IN ar_cash_receipts.receipt_date%TYPE ) IS
2687 BEGIN
2688     IF PG_DEBUG in ('Y', 'C') THEN
2689        arp_standard.debug( 'arp_calculate_discount.validate_args_discounts_cover()+' );
2690     END IF;
2691     --
2692     IF ( p_mode is NULL OR p_invoice_currency_code IS NULL OR
2693          p_ps_id IS NULL OR p_trx_date IS NULL OR
2694          p_apply_date IS NULL ) THEN
2695          FND_MESSAGE.set_name ('AR', 'AR_ARGUEMENTS_FAIL' );
2696          APP_EXCEPTION.raise_exception;
2697     END IF;
2698     --
2699     IF PG_DEBUG in ('Y', 'C') THEN
2700        arp_standard.debug( 'arp_calculate_discount.validate_args_discounts_cover()-' );
2701     END IF;
2702     --
2703     EXCEPTION
2704          WHEN OTHERS THEN
2705               IF PG_DEBUG in ('Y', 'C') THEN
2706                  arp_standard.debug('validate_args_discounts_cover: ' ||
2707                    'EXCEPTION: arp_calculate_discount.validate_args_calc_discoun
2708 ts' );
2709               END IF;
2710               RAISE;
2711 END validate_args_discounts_cover;
2712 
2713 -- AR/TA Changes
2714 PROCEDURE set_g_called_from (p_called_from IN varchar2) IS
2715 
2716 BEGIN
2717      IF ( p_called_from = 'MANUAL') THEN
2718         arp_calculate_discount.g_called_from := 'MANUAL' ;
2719      END IF ;
2720 
2721 EXCEPTION
2722      WHEN OTHERS THEN
2723           NULL ;
2724 END SET_G_CALLED_FROM ;
2725 --
2726 --
2727 END arp_calculate_discount;