DBA Data[Home] [Help]

PACKAGE BODY: APPS.ARP_CALCULATE_DISCOUNT

Source


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