DBA Data[Home] [Help]

PACKAGE BODY: APPS.AR_IREC_PAYMENTS

Source


1 PACKAGE BODY AR_IREC_PAYMENTS AS
2 /* $Header: ARIRPMTB.pls 120.55.12010000.10 2009/02/13 09:06:05 avepati ship $ */
3 
4 /*=======================================================================+
5  |  Package Global Constants
6  +=======================================================================*/
7 G_PKG_NAME      CONSTANT VARCHAR2(30)    := 'AR_IREC_PAYMENTS';
8 
9 
10 TYPE INVOICE_REC_TYPE IS RECORD
11      (PAYMENT_SCHEDULE_ID     NUMBER(15),
12       PAYMENT_AMOUNT		  NUMBER,
13       CUSTOMER_ID             NUMBER(15),
14       ACCOUNT_NUMBER          VARCHAR2(30),
15       CUSTOMER_TRX_ID         NUMBER(15),
16       CURRENCY_CODE           VARCHAR2(15),
17       SERVICE_CHARGE          NUMBER
18      );
19 
20 TYPE INVOICE_LIST_TABTYPE IS TABLE OF INVOICE_REC_TYPE;
21 
22 
23 /*========================================================================
24  | Prototype Declarations Procedures
25  *=======================================================================*/
26 
27   PG_DEBUG varchar2(1) := NVL(FND_PROFILE.value('AFLOG_ENABLED'), 'N');
28 
29 
30   FUNCTION get_iby_account_type(p_account_type        IN VARCHAR2) RETURN VARCHAR2;
31 
32   PROCEDURE write_debug_and_log(p_message IN VARCHAR2);
33 
34   PROCEDURE write_API_output(p_msg_count        IN NUMBER,
35                              p_msg_data         IN VARCHAR2);
36 
37   PROCEDURE apply_service_charge ( p_customer_id		  IN NUMBER,
38                                    p_site_use_id          IN NUMBER DEFAULT NULL,
39                                    x_return_status        OUT NOCOPY VARCHAR2);
40 
41   PROCEDURE apply_cash ( p_customer_id		    IN NUMBER,
42                          p_site_use_id          IN NUMBER DEFAULT NULL,
43                          p_cash_receipt_id      IN NUMBER,
44                          p_return_status         OUT NOCOPY VARCHAR2,
45                          p_apply_err_count       OUT NOCOPY NUMBER,
46                          x_msg_count           OUT NOCOPY NUMBER,
47                          x_msg_data            OUT NOCOPY VARCHAR2
48                        );
49 
50   PROCEDURE create_receipt (p_payment_amount        IN NUMBER,
51                             p_customer_id           IN NUMBER,
52                             p_site_use_id           IN NUMBER,
53                             p_bank_account_id       IN NUMBER,
54                             p_receipt_date          IN DATE DEFAULT trunc(SYSDATE),
55                             p_receipt_method_id     IN NUMBER,
56                             p_receipt_currency_code IN VARCHAR2,
57                             p_receipt_exchange_rate IN NUMBER,
58                             p_receipt_exchange_rate_type IN VARCHAR2,
59                             p_receipt_exchange_rate_date IN DATE,
60                             p_trxn_extn_id	    IN NUMBER,
61                             p_cash_receipt_id       OUT NOCOPY NUMBER,
62                             p_status                OUT NOCOPY VARCHAR2,
63                             x_msg_count           OUT NOCOPY NUMBER,
64                             x_msg_data            OUT NOCOPY VARCHAR2);
65 
66   PROCEDURE process_payment(
67 		p_cash_receipt_id     IN  NUMBER,
68 	        p_payer_rec           IN  IBY_FNDCPT_COMMON_PUB.PayerContext_rec_type,
69 	        P_payee_rec           IN  IBY_FNDCPT_TRXN_PUB.PayeeContext_rec_type,
70                 p_called_from         IN  VARCHAR2,
71                 p_response_error_code OUT NOCOPY VARCHAR2,
72                 x_msg_count           OUT NOCOPY NUMBER,
73                 x_msg_data            OUT NOCOPY VARCHAR2,
74 	        x_return_status       OUT NOCOPY VARCHAR2
75                            );
76 
77  PROCEDURE update_cc_bill_to_site(
78 		p_cc_location_rec	IN   HZ_LOCATION_V2PUB.LOCATION_REC_TYPE,
79 		x_cc_bill_to_site_id	IN  NUMBER,
80 		x_return_status		OUT NOCOPY VARCHAR2,
81 		x_msg_count		OUT NOCOPY NUMBER,
82 		x_msg_data		OUT NOCOPY VARCHAR2);
83 
84 /*========================================================================
85  | Prototype Declarations Functions
86  *=======================================================================*/
87 /*========================================================================
88  | PUBLIC function get_credit_card_type
89  |
90  | DESCRIPTION
91  |      Determines if a credit card number is valid
92  |      ----------------------------------------
93  |
94  | PSEUDO CODE/LOGIC
95  |
96  |
97  |
98  |
99  | PARAMETERS
100  |      credit_card_number   IN      Credit card number --
101  |                                   without white spaces
102  |
103  | RETURNS
104  |      TRUE  if credit card number is valid
105  |      FALSE if credit card number is invalid
106  |
107  | KNOWN ISSUES
108  |
109  |
110  |
111  | NOTES
112  |
113  |
114  |
115  | MODIFICATION HISTORY
116  | Date                  Author            Description of Changes
117  | 23-JAN-2001           O Steinmeier      Created
118  |
119  *=======================================================================*/
120 FUNCTION is_credit_card_number_valid(  p_credit_card_number IN  VARCHAR2 )
121          RETURN NUMBER IS
122 
123 
124   TYPE numeric_tab_typ IS TABLE of number INDEX BY BINARY_INTEGER;
125   TYPE character_tab_typ IS TABLE of char(1) INDEX BY BINARY_INTEGER;
126 
127   l_stripped_num_table		numeric_tab_typ;   /* Holds credit card number stripped of white spaces */
128   l_product_table		numeric_tab_typ;   /* Table of cc digits multiplied by 2 or 1,for validity check */
129   l_len_credit_card_num   	number := 0;  	   /* Length of credit card number stripped of white spaces */
130   l_product_tab_sum   		number := 0;  	   /* Sum of digits in product table */
131   l_actual_cc_check_digit       number := 0;  	   /* First digit of credit card, numbered from right to left */
132   l_mod10_check_digit        	number := 0;  	   /* Check digit after mod10 algorithm is applied */
133   j 				number := 0;  	   /* Product table index */
134   BEGIN
135 	arp_util.debug('ar_irec_payments_pkg.is_credit_card_number_valid()+0');
136 
137 	SELECT lengthb(p_credit_card_number)
138 	INTO   l_len_credit_card_num
139 	FROM   dual;
140 
141 	FOR i in 1..l_len_credit_card_num LOOP
142 		SELECT to_number(substrb(p_credit_card_number,i,1))
143 		INTO   l_stripped_num_table(i)
144 		FROM   dual;
145 	END LOOP;
146 	l_actual_cc_check_digit := l_stripped_num_table(l_len_credit_card_num);
147 
148 	FOR i in 1..l_len_credit_card_num-1 LOOP
149 		IF ( mod(l_len_credit_card_num+1-i,2) > 0 )
150 		THEN
151 		    -- Odd numbered digit.  Store as is, in the product table.
152 		    j := j+1;
153 	 	    l_product_table(j) := l_stripped_num_table(i);
154 		ELSE
155 		    -- Even numbered digit.  Multiply digit by 2 and store in the product table.
156 		    -- Numbers beyond 5 result in 2 digits when multiplied by 2. So handled seperately.
157 	            IF (l_stripped_num_table(i) >= 5)
158 		    THEN
159 		         j := j+1;
160 	 		 l_product_table(j) := 1;
161 		         j := j+1;
162 	 		 l_product_table(j) := (l_stripped_num_table(i) - 5) * 2;
163 		    ELSE
164 		         j := j+1;
165 	 		 l_product_table(j) := l_stripped_num_table(i) * 2;
166 		    END IF;
167 		END IF;
168 	END LOOP;
169 
170 	-- Sum up the product table's digits
171 	FOR k in 1..j LOOP
172 		l_product_tab_sum := l_product_tab_sum + l_product_table(k);
173 	END LOOP;
174 
175 	l_mod10_check_digit := mod( (10 - mod( l_product_tab_sum, 10)), 10);
176 
177 	-- If actual check digit and check_digit after mod10 don't match, the credit card is an invalid one.
178 	IF ( l_mod10_check_digit <> l_actual_cc_check_digit)
179 	THEN
180 		arp_util.debug('Card is Valid');
181 		arp_util.debug('ar_irec_payments_pkg.is_credit_card_number_valid()-');
182 		return(0);
183 	ELSE
184 		arp_util.debug('Card is not Valid');
185 		arp_util.debug('ar_irec_payments_pkg.is_credit_card_number_valid()-');
186 		return(1);
187 	END IF;
188 
189 END is_credit_card_number_valid;
190 
191 
192 /*========================================================================
193  | PUBLIC function get_credit_card_type
194  |
195  | DESCRIPTION
196  |      Determines for a given credit card number the credit card type.
197  |      ----------------------------------------
198  |
199  | PSEUDO CODE/LOGIC
200  |
201  | PARAMETERS
202  |      credit_card_number   IN      Credit card number
203  |
204  | RETURNS
205  |      credit_card type (based on lookup type  AR_IREC_CREDIT_CARD_TYPE
206  |
207  | KNOWN ISSUES
208  |
209  |
210  |
211  | NOTES
212  |
213  |
214  |
215  | MODIFICATION HISTORY
216  | Date                  Author            Description of Changes
217  | 22-JAN-2001           O Steinmeier      Created
218  | 11-AUG-2008          avepati             Bug 6493495 - TST1203.XB5.QA: CREDIT CARD PAYMENT NOT WORKING
219  |
220  *=======================================================================*/
221 FUNCTION get_credit_card_type(  p_credit_card_number IN  VARCHAR2 )
222          RETURN VARCHAR2 IS
223 
224   /*-----------------------------------------------------------------------+
225  | Use for file debug or standard output debug                           |
226  +-----------------------------------------------------------------------*/
227 
228 --   arp_standard.debug('AR_IREC_PAYMENTS.get_credit_card_type()+');
229 
230 --   arp_standard.debug(' p_credit_card_number :' || p_credit_card_number);
231 
232    l_card_issuer     iby_creditcard_issuers_b.card_issuer_code%TYPE;
233    l_issuer_range   iby_cc_issuer_ranges.cc_issuer_range_id%TYPE;
234    l_card_prefix    iby_cc_issuer_ranges.card_number_prefix%TYPE;
235    l_digit_check    iby_creditcard_issuers_b.digit_check_flag%TYPE;
236 
237  CURSOR c_range
238     (ci_card_number IN iby_creditcard.ccnumber%TYPE,
239      ci_card_len IN NUMBER)
240     IS
241       SELECT cc_issuer_range_id, r.card_issuer_code,
242         card_number_prefix, NVL(digit_check_flag,'N')
243       FROM iby_cc_issuer_ranges r, iby_creditcard_issuers_b i
244       WHERE (card_number_length = ci_card_len)
245         AND (INSTR(ci_card_number,card_number_prefix) = 1)
246         AND (r.card_issuer_code = i.card_issuer_code);
247   BEGIN
248     IF (c_range%ISOPEN) THEN CLOSE c_range; END IF;
249 
250     OPEN c_range(p_credit_card_number,LENGTH(p_credit_card_number));
251     FETCH c_range INTO l_issuer_range, l_card_issuer,
252       l_card_prefix, l_digit_check;
253     CLOSE c_range;
254 
255 --   arp_standard.debug(' l_card_issuer  :' || l_card_issuer);
256 
257     IF (l_card_issuer IS NULL) THEN
258       l_card_issuer := 'UNKNOWN';
259       l_digit_check := 'N';
260     END IF;
261     RETURN  l_card_issuer;
262 END get_credit_card_type;
263 
264 /*========================================================================
265  | PUBLIC function get_exchange_rate
266  |
267  | DESCRIPTION
268  |      Returns exchange rate information
269  |      ----------------------------------------
270  |
271  | PSEUDO CODE/LOGIC
272  |
273  | PARAMETERS
274  |
275  |
276  |
277  |
278  |
279  | RETURNS
280  |
281  |
282  | KNOWN ISSUES
283  |
284  |
285  |
286  | NOTES
287  |
288  |
289  |
290  | MODIFICATION HISTORY
291  | Date                  Author            Description of Changes
292  | 27-FEB-2001           O Steinmeier      Created
293  |
294  *=======================================================================*/
295 
296  PROCEDURE get_exchange_rate(
297               p_trx_currency_code   IN VARCHAR2,
298               p_trx_exchange_rate   IN NUMBER,
299               p_def_exchange_rate_date  IN DATE DEFAULT trunc(SYSDATE),
300               p_exchange_rate       OUT NOCOPY NUMBER,
301               p_exchange_rate_type  OUT NOCOPY VARCHAR2,
302               p_exchange_rate_date  OUT NOCOPY DATE) IS
303 
304 
305    l_fixed_rate     VARCHAR2(30);
306    l_procedure_name VARCHAR2(30);
307    l_debug_info	    VARCHAR2(200);
308 
309  BEGIN
310 
311    l_procedure_name := '.get_exchange_rate';
312 
313    -- By default set the exchange rate date to the proposed default.
314    --------------------------------------------------------------------------------
315    l_debug_info := 'Set the exchange rate date to the proposed default';
316    --------------------------------------------------------------------------------
317    p_exchange_rate_date := p_def_exchange_rate_date;
318 
319    -- first check if invoice is in foreign currency:
320 
321    if (p_trx_currency_code = arp_global.functional_currency) then
322 
323      -- trx currency is base currency; no exchange rate needed.
324      --------------------------------------------------------------------------------
325      l_debug_info := 'Transaction currency is base currency; no exchange rate needed';
326      --------------------------------------------------------------------------------
327      IF (PG_DEBUG = 'Y') THEN
328         arp_standard.debug('Trx currency is functional --> no exchange rate');
329      END IF;
330 
331      p_exchange_rate := NULL;
332      p_exchange_rate_type := NULL;
333      p_exchange_rate_date := NULL;
334 
335      RETURN;
336 
337    end if;
338 
339    -- check if currencies have fixed-rate relationship
340    --------------------------------------------------------------------------------
341    l_debug_info := 'Check if currencies have fixed-rate relationship';
342    --------------------------------------------------------------------------------
343    l_fixed_rate := gl_currency_api.is_fixed_rate(
344                          p_trx_currency_code,
345                          arp_global.functional_currency,
346                          p_exchange_rate_date);
347 
348    if l_fixed_rate = 'Y' then
349      --------------------------------------------------------------------------
350      l_debug_info := 'Exchange rate is fixed';
351      --------------------------------------------------------------------------
352      IF (PG_DEBUG = 'Y') THEN
353         arp_standard.debug('Fixed Rate');
354      END IF;
355 
356      p_exchange_rate_type := 'EMU FIXED';
357 
358      /* no need to get rate; rct api will get it anyway
359 
360      p_exchange_rate := arpcurr.getrate
361              (p_trx_currency_code,
362               arp_global.functional_currency,
363               p_exchange_rate_date,
364               p_exchange_rate_type);
365 
366      */
367 
368      IF (PG_DEBUG = 'Y') THEN
369         arp_standard.debug('Rate = ' || to_char(p_exchange_rate));
370      END IF;
371 
372    else  -- exchange rate is not fixed --> check profile for default type
373 
374      -------------------------------------------------------------------------------------
375      l_debug_info := 'Exchange rate is not fixed - check profile option for default type';
376      -------------------------------------------------------------------------------------
377      IF (PG_DEBUG = 'Y') THEN
378         arp_standard.debug('No Fixed Rate');
379      END IF;
380      p_exchange_rate_type := fnd_profile.value('AR_DEFAULT_EXCHANGE_RATE_TYPE');
381 
382      IF (PG_DEBUG = 'Y') THEN
383         arp_standard.debug('Profile option default exch rate type: '|| p_exchange_rate_type);
384      END IF;
385 
386      if (p_exchange_rate_type IS NOT NULL) then
387 
388        -- try to get exchange rate from GL for this rate type
389        -------------------------------------------------------------------------------------------
390        l_debug_info := 'Exchange rate type obtained from profile option - get exchange rate from GL';
391        -------------------------------------------------------------------------------------------
392        p_exchange_rate :=  arpcurr.getrate
393                (p_trx_currency_code,
394                 arp_global.functional_currency,
395                 p_exchange_rate_date,
396                 p_exchange_rate_type);
397 
398        IF (PG_DEBUG = 'Y') THEN
399           arp_standard.debug('Rate = ' || to_char(p_exchange_rate));
400        END IF;
401 
402        if p_exchange_rate = -1 then -- no rate found in GL
403 
404          -------------------------------------------------------------------------------------------
405          l_debug_info := 'Exchange rate not found in GL- use invoice exchange rate';
406          -------------------------------------------------------------------------------------------
407          IF (PG_DEBUG = 'Y') THEN
408             arp_standard.debug('no conversion rate found... using trx rate');
409          END IF;
410 
411          p_exchange_rate_type := 'User';
412          p_exchange_rate := p_trx_exchange_rate;
413 
414        else -- rate was successfully derived --> null it out so
415             -- rct api can rederive it (it doesn't allow a derivable rate
416             -- to be passed in!)
417 
418            p_exchange_rate := NULL;
419 
420 
421        end if;
422 
423      else -- rate type profile is not set --> use invoice exchange rate
424        -------------------------------------------------------------------------------------------
425        l_debug_info := 'Rate type profile not set - use invoice exchange rate';
426        -------------------------------------------------------------------------------------------
427        p_exchange_rate_type := 'User';
428        p_exchange_rate := p_trx_exchange_rate;
429 
430      end if;
431 
432    end if; -- fixed/non-fixed rate case
433 
434      IF (PG_DEBUG = 'Y') THEN
435         arp_standard.debug('Leaving get_exchange_rate: ');
436         arp_standard.debug('p_exchange_rate_type = ' || p_exchange_rate_type);
437         arp_standard.debug('p_exchange_rate      = ' || to_char(p_exchange_rate));
438      END IF;
439 
440  EXCEPTION
441     WHEN OTHERS THEN
442       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
443       write_debug_and_log('- Transaction Currency Code: '||p_trx_currency_code);
444       write_debug_and_log('- Transaction Exchange Rate: '||p_trx_exchange_rate);
445       write_debug_and_log('- Exchange Rate found: '||p_exchange_rate);
446       write_debug_and_log('ERROR =>'|| SQLERRM);
447 
448       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
449       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
450       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
451       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
452       FND_MSG_PUB.ADD;
453 
454  END get_exchange_rate;
455 
456 
457 /*========================================================================
458  | PUBLIC function get_payment_information
459  |
460  | DESCRIPTION
461  |      Returns payment method and remittance bank information
462  |      ----------------------------------------
463  |
464  | PSEUDO CODE/LOGIC
465  |
466  | PARAMETERS
467  |
468  |
469  |
470  |
471  |
472  | RETURNS
473  |
474  |
475  | KNOWN ISSUES
476  |
477  |
478  |
479  | NOTES
480  |
481  |
482  |
483  | MODIFICATION HISTORY
484  | Date                  Author            Description of Changes
485  | 13-FEB-2001           O Steinmeier      Created
486  | 26-APR-2004           vnb               Bug # 3467287 - Customer Site ID made an input
487  |										   parameter.
488  | 22-JUN-2007		 mbolli		   Bug#6109909 - Not using 'Payment Method' set at
489  |					     customer/site level
490  |
491  *=======================================================================*/
492 
493 PROCEDURE  get_payment_information(
494                   p_customer_id		    IN NUMBER,
495                   p_site_use_id             IN NUMBER DEFAULT NULL,
496 		  p_payment_schedule_id     IN NUMBER,
497                   p_payment_instrument      IN VARCHAR2,
498                   p_trx_date                IN DATE,
499          	  p_currency_code           OUT NOCOPY VARCHAR2,
500                   p_exchange_rate           OUT NOCOPY VARCHAR2,
501           	  p_receipt_method_id       OUT NOCOPY NUMBER,
502            	  p_remit_bank_account_id   OUT NOCOPY NUMBER,
503            	  p_receipt_creation_status OUT NOCOPY VARCHAR2,
504                   p_trx_number              OUT NOCOPY VARCHAR2,
505 		  p_payment_channel_code    OUT NOCOPY VARCHAR2
506                   ) IS
507 
508 
509 CURSOR payment_method_info_cur IS
510    SELECT rm.receipt_method_id receipt_method_id, rm.payment_channel_code payment_channel_code,
511           rc.creation_status receipt_creation_status
512    FROM   ar_system_parameters sp,
513           ar_receipt_classes rc,
514           ar_receipt_methods rm
515    WHERE  rm.receipt_method_id = decode(p_payment_instrument,                        /* J Rautiainen ACH Implementation */
516                                        'BANK_ACCOUNT', sp.irec_ba_receipt_method_id, /* J Rautiainen ACH Implementation */
517                                         sp.irec_cc_receipt_method_id)                /* J Rautiainen ACH Implementation */
518       AND rm.receipt_class_id = rc.receipt_class_id;
519 
520   --Bug3186314: Cursor to get the payment method at customer/site level.
521   CURSOR cust_payment_method_info_cur(p_siteuseid NUMBER, p_currcode VARCHAR2) IS
522    SELECT arm.receipt_method_id receipt_method_id, arm.payment_channel_code payment_channel_code,
523           arc.creation_status receipt_creation_status
524    FROM      ar_receipt_methods         arm,
525              ra_cust_receipt_methods    rcrm,
526              ar_receipt_method_accounts arma,
527              ce_bank_acct_uses_ou_v          aba,
528              ce_bank_accounts           cba,
529              ar_receipt_classes         arc
530    WHERE     arm.receipt_method_id = rcrm.receipt_method_id
531    AND       arm.receipt_method_id = arma.receipt_method_id
532    AND       arm.receipt_class_id  = arc.receipt_class_id
533    AND       rcrm.customer_id      = p_customer_id
534    AND       arma.remit_bank_acct_use_id = aba.bank_acct_use_id
535    AND       aba.bank_account_id = cba.bank_account_id
536    AND
537              (
538                  NVL(rcrm.site_use_id,
539                      p_siteuseid)   = p_siteuseid
540                OR
541                  (
542                         p_siteuseid IS NULL
543                    AND  rcrm.site_use_id  IS NULL
544                  )
545              )
546 --Bug#6109909
547    --AND       rcrm.primary_flag          = 'Y'
548    AND       (
549                  cba.currency_code    =
550                              p_currcode OR
551                  cba.receipt_multi_currency_flag = 'Y'
552              )
553    AND      (
554                  (    p_payment_instrument = 'BANK_ACCOUNT'
555 --Bug 6024713: Choose 'NONE' if arm.payment_type_code is NULL
556 --Bug#6109909:
557       -- In 11i The 'PaymentMethod' in UI maps to 'payment_type_code' column of table ar_receipts_methods
558       -- and in R12, it maps to 'payment_channel_code' whose values are taken from IBY sources.
559       -- In R12, the 'payment_type_code' is 'NONE' for new records.
560       -- AND In R12, Here we are not handling the code for the other payment Methods like Bills Receivable, Debit Card etc..,
561 
562              --  and nvl(arm.payment_type_code, 'NONE') <> 'CREDIT_CARD'
563                   and arm.payment_channel_code <> 'CREDIT_CARD'
564                   and arc.remit_flag = 'Y'
565                   and arc.confirm_flag = 'N')
566              OR  (    p_payment_instrument <> 'BANK_ACCOUNT'
567     --Bug#6109909
568                 --and nvl(arm.payment_type_code, 'NONE') = 'CREDIT_CARD')
569                   and arm.payment_channel_code = 'CREDIT_CARD')
570             )
571 
572   -- Bug#6109909:
573      -- In R12,Currency code is not mandatory on the customer bank account and so removing the
574      -- below condition.
575      -- Observations for the below condition, if it requires in future:
576      -- a. The where caluse criteria 'party_id = p_customer_id' should be replaced
577      --    with 'cust_account_id = p_customer_id'
578      -- b. For 'AUTOMATIC' creation methods, Don't validate the currencyCode for
579      -- 'Credit Card' instrucment types. Here validate only for 'BankAccount'
580 
581   /*
582 
583    AND      ( arc.creation_method_code = 'MANUAL' or
584             ( arc.creation_method_code = 'AUTOMATIC' and
585 --Bug 4947418: Modified the following query as ar_customer_bank_accounts_v
586 --has been obsoleted in r12.
587               p_currcode in (select currency_code from
588 		iby_fndcpt_payer_assgn_instr_v
589 		where party_id=p_customer_id)))
590    */
591 
592 
593    -- AND       aba.set_of_books_id = arp_trx_global.system_info.system_parameters.set_of_books_id
594    AND       TRUNC(nvl(aba.end_date,
595                          p_trx_date)) >=
596              TRUNC(p_trx_date)
597 --Bug 6024713: Added TRUNC for the left side for the below 3 criterias
598    AND       TRUNC(p_trx_date) between
599                       TRUNC(nvl(
600                                    arm.start_date,
601                                   p_trx_date))
602                   and TRUNC(nvl(
603                                   arm.end_date,
604                                   p_trx_date))
605    AND       TRUNC(p_trx_date) between
606                       TRUNC(nvl(
607                                    rcrm.start_date,
608                                   p_trx_date))
609                   and TRUNC(nvl(
610                                   rcrm.end_date,
611                                   p_trx_date))
612    AND       TRUNC(p_trx_date) between
613                       TRUNC(arma.start_date)
614                   and TRUNC(nvl(
615                                   arma.end_date,
616                                   p_trx_date))
617               ORDER BY rcrm.primary_flag DESC;
618 
619 --Bug 6339265 : Cursor to get CC Payment Method set in the profile OIR_CC_PMT_METHOD.
620  CURSOR cc_profile_pmt_method_info_cur IS
621   SELECT arm.receipt_method_id receipt_method_id,
622     arc.creation_status receipt_creation_status
623   FROM ar_receipt_methods arm,
624     ar_receipt_method_accounts arma,
625     ce_bank_acct_uses_ou_v aba,
626     ce_bank_accounts       cba,
627     ar_receipt_classes arc
628   WHERE arm.payment_channel_code = 'CREDIT_CARD'
629     AND arm.receipt_method_id = NVL( to_number(fnd_profile.VALUE('OIR_CC_PMT_METHOD')), arm.receipt_method_id)
630     AND arm.receipt_method_id = arma.receipt_method_id
631     AND arm.receipt_class_id = arc.receipt_class_id
632     AND arma.remit_bank_acct_use_id = aba.bank_acct_use_id
633     AND aba.bank_account_id = cba.bank_account_id
634     AND (cba.currency_code = p_currency_code OR cba.receipt_multi_currency_flag = 'Y')
635     AND TRUNC(nvl(aba.end_date,p_trx_date)) >= TRUNC(p_trx_date)
636     AND TRUNC(p_trx_date) BETWEEN TRUNC(nvl(arm.start_date,   p_trx_date)) AND TRUNC(nvl(arm.end_date,   p_trx_date))
637     AND TRUNC(p_trx_date) BETWEEN TRUNC(arma.start_date) AND TRUNC(nvl(arma.end_date,   p_trx_date));
638 
639   --Bug 6339265 : Cursor to get Bank Acount Payment Method set in the profile OIR_BA_PMT_METHOD.
640  CURSOR ba_profile_pmt_method_info_cur IS
641   SELECT arm.receipt_method_id receipt_method_id,
642     arc.creation_status receipt_creation_status
643   FROM ar_receipt_methods arm,
644     ar_receipt_method_accounts arma,
645     ce_bank_acct_uses_ou_v aba,
646     ce_bank_accounts       cba,
647     ar_receipt_classes arc
648   WHERE NVL(arm.payment_channel_code,'NONE') <> 'CREDIT_CARD'
649     AND arm.receipt_method_id = NVL( to_number(fnd_profile.VALUE('OIR_BA_PMT_METHOD')), arm.receipt_method_id)
650     AND arm.receipt_method_id = arma.receipt_method_id
651     AND arm.receipt_class_id = arc.receipt_class_id
652     AND arma.remit_bank_acct_use_id = aba.bank_acct_use_id
653     AND aba.bank_account_id = cba.bank_account_id
654     AND (cba.currency_code = p_currency_code OR cba.receipt_multi_currency_flag = 'Y')
655     AND TRUNC(nvl(aba.end_date,p_trx_date)) >= TRUNC(p_trx_date)
656     AND TRUNC(p_trx_date) BETWEEN TRUNC(nvl(arm.start_date,   p_trx_date)) AND TRUNC(nvl(arm.end_date,   p_trx_date))
657     AND TRUNC(p_trx_date) BETWEEN TRUNC(arma.start_date) AND TRUNC(nvl(arma.end_date,   p_trx_date));
658 
659 CURSOR payment_schedule_info_cur IS
660    SELECT customer_site_use_id, invoice_currency_code, exchange_rate,trx_number
661    FROM   ar_payment_schedules
662    WHERE  payment_schedule_id = p_payment_schedule_id;
663 
664    payment_method_info    payment_method_info_cur%ROWTYPE;
665    payment_schedule_info  payment_schedule_info_cur%ROWTYPE;
666    cust_payment_method_info  cust_payment_method_info_cur%ROWTYPE;
667    cc_profile_pmt_method_info cc_profile_pmt_method_info_cur%ROWTYPE;
668    ba_profile_pmt_method_info ba_profile_pmt_method_info_cur%ROWTYPE;
669 
670   l_customer_id		RA_CUST_RECEIPT_METHODS.CUSTOMER_ID%TYPE;
671   l_site_use_id		RA_CUST_RECEIPT_METHODS.SITE_USE_ID%TYPE;
672   l_currency_code	AR_PAYMENT_SCHEDULES_ALL.INVOICE_CURRENCY_CODE%TYPE;
673 
674   l_procedure_name VARCHAR2(30);
675   l_debug_info	   VARCHAR2(200);
676 
677 BEGIN
678 
679    l_procedure_name := '.get_payment_information';
680 
681    --------------------------------------------------------------------
682    l_debug_info := 'Get payment schedule information';
683    --------------------------------------------------------------------
684    OPEN payment_schedule_info_cur;
685    FETCH payment_schedule_info_cur INTO payment_schedule_info;
686    close payment_schedule_info_cur;
687 
688    l_currency_code := payment_schedule_info.invoice_currency_code;
689    l_site_use_id   := payment_schedule_info.customer_site_use_id;
690    p_trx_number    := payment_schedule_info.trx_number;
691    p_exchange_rate := payment_schedule_info.exchange_rate;
692 
693    -- ### required change: error handling
694    -- ### in case the query fails.
695 
696   --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
697   if (p_payment_schedule_id is null ) then
698     -- this is the case for multiple invoices.
699     ------------------------------------------------------------------------
700     l_debug_info := 'There are multiple invoices: get customer information';
701     ------------------------------------------------------------------------
702     BEGIN
703       select customer_id,customer_site_use_id,currency_code into l_customer_id,l_site_use_id,l_currency_code
704       from AR_IREC_PAYMENT_LIST_GT
705       where customer_id = p_customer_id
706       and customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id);
707       EXCEPTION
708         when others then
709           IF (PG_DEBUG = 'Y') THEN
710             arp_standard.debug('There may be invoices with different sites');
711           END IF;
712     END;
713     if ( l_customer_id is null ) then
714      --Code should not come here ideally
715      BEGIN
716         select currency_code into l_currency_code
717         from AR_IREC_PAYMENT_LIST_GT
718         group by currency_code;
719         EXCEPTION
720           when others then
721             IF (PG_DEBUG = 'Y') THEN
722               arp_standard.debug('There may be invoices with different currencies');
723             END IF;
724       END;
725     end if;
726   end if;
727 
728   -- IF Customer Site Use Id is -1 then it is to be set as null
729   IF ( l_site_use_id = -1 ) THEN
730     l_site_use_id := NULL;
731   END IF;
732 
733     IF (p_payment_instrument <> 'BANK_ACCOUNT') THEN
734 	  ---------------------------------------------------------------------------------
735 	  l_debug_info := 'Get payment method information from the OIR_CC_PMT_METHOD profile';
736 	  ---------------------------------------------------------------------------------
737 	  IF (fnd_profile.VALUE('OIR_CC_PMT_METHOD') IS NOT NULL AND fnd_profile.VALUE('OIR_CC_PMT_METHOD') <> 'DISABLED') THEN
738 
739             BEGIN
740 
741 		  OPEN  cc_profile_pmt_method_info_cur;
742 		  FETCH cc_profile_pmt_method_info_cur INTO cc_profile_pmt_method_info;
743 
744 	      /* If CC Payment Method set is NULL or DISABLED or an invalid payment method, it returns NO rows */
745 
746 		  IF cc_profile_pmt_method_info_cur%FOUND THEN
747 		    p_receipt_creation_status	:=  cc_profile_pmt_method_info.receipt_creation_status;
748 		    p_receipt_method_id		:=  cc_profile_pmt_method_info.receipt_method_id;
749 		  END IF;
750 
751 		  CLOSE cc_profile_pmt_method_info_cur;
752 
753             EXCEPTION
754               WHEN OTHERS THEN
755                 l_debug_info := 'Invalid Payment Method is Set in the profile OIR_CC_PMT_METHOD. Value in profile=' ||  fnd_profile.VALUE('OIR_CC_PMT_METHOD');
756 		     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
757 		        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info
758                                             ||':ERROR =>'|| SQLERRM);
759 		     end if;
760             END;
761 
762 	  END IF;
763   END IF;
764 
765   IF (p_payment_instrument <> 'CREDIT_CARD') THEN
766 	  ---------------------------------------------------------------------------------
767 	  l_debug_info := 'Get payment method information from the OIR_BA_PMT_METHOD profile';
768 	  ---------------------------------------------------------------------------------
769 	  IF (fnd_profile.VALUE('OIR_BA_PMT_METHOD') IS NOT NULL AND fnd_profile.VALUE('OIR_BA_PMT_METHOD') <> 'DISABLED') THEN
770 
771             BEGIN
772 
773 		  OPEN  ba_profile_pmt_method_info_cur;
774 		  FETCH ba_profile_pmt_method_info_cur INTO ba_profile_pmt_method_info;
775 
776 	      /* If BA Payment Method set is NULL or DISABLED or an invalid payment method, it returns NO rows */
777 
778 		  IF ba_profile_pmt_method_info_cur%FOUND THEN
779 		    p_receipt_creation_status	:=  ba_profile_pmt_method_info.receipt_creation_status;
780 		    p_receipt_method_id		:=  ba_profile_pmt_method_info.receipt_method_id;
781 		  END IF;
782 
783 		  CLOSE ba_profile_pmt_method_info_cur;
784 
785             EXCEPTION
786               WHEN OTHERS THEN
787                 l_debug_info := 'Invalid Payment Method is Set in the profile OIR_BA_PMT_METHOD. Value in profile=' ||  fnd_profile.VALUE('OIR_BA_PMT_METHOD');
788 		     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
789 		        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info
790                                             ||':ERROR =>'|| SQLERRM);
791 		     end if;
792             END;
793 
794 	  END IF;
795   END IF;
796 
797   IF ( p_receipt_method_id IS NULL ) THEN
798 
799   ---------------------------------------------------------------------------------
800   l_debug_info := 'Get payment method information from the relevant customer site';
801   ---------------------------------------------------------------------------------
802   OPEN  cust_payment_method_info_cur(l_site_use_id, l_currency_code);
803   FETCH cust_payment_method_info_cur INTO cust_payment_method_info;
804 
805   IF cust_payment_method_info_cur%FOUND THEN
806     p_receipt_creation_status := cust_payment_method_info.receipt_creation_status;
807     p_receipt_method_id := cust_payment_method_info.receipt_method_id;
808     p_payment_channel_code := cust_payment_method_info.payment_channel_code;
809   END IF;
810   CLOSE cust_payment_method_info_cur;
811  END IF;
812 
813   if ( p_receipt_method_id is null ) then
814     ----------------------------------------------------------------------------------------
815     l_debug_info := 'Get payment method information from the customer at the account level';
816     ----------------------------------------------------------------------------------------
817     l_site_use_id := NULL;
818     OPEN  cust_payment_method_info_cur(l_site_use_id, l_currency_code);
819     FETCH cust_payment_method_info_cur INTO cust_payment_method_info;
820 
821     IF cust_payment_method_info_cur%FOUND THEN
822       p_receipt_creation_status := cust_payment_method_info.receipt_creation_status;
823       p_receipt_method_id := cust_payment_method_info.receipt_method_id;
824       p_payment_channel_code := cust_payment_method_info.payment_channel_code;
825     END IF;
826     CLOSE cust_payment_method_info_cur;
827   end if;
828 
829   if ( p_receipt_method_id is null ) then
830     -- get from system parameters
831     ----------------------------------------------------------------------------------------
832     l_debug_info := 'Get payment method information from the system parameters';
833     ----------------------------------------------------------------------------------------
834     OPEN  payment_method_info_cur;
835     FETCH payment_method_info_cur INTO payment_method_info;
836 
837     IF payment_method_info_cur%FOUND THEN
838       p_receipt_creation_status := payment_method_info.receipt_creation_status;
839       p_receipt_method_id := payment_method_info.receipt_method_id;
840       p_payment_channel_code := payment_method_info.payment_channel_code;
841     END IF;
842     CLOSE payment_method_info_cur;
843   end if;
844 
845   --Bug # 3467287 - p_site_use_id is made an input parameter.
846   --p_site_use_id   := l_site_use_id;
847   p_currency_code := l_currency_code;
848 
849 EXCEPTION
850     WHEN OTHERS THEN
851       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
852       write_debug_and_log('- Customer Id: '||p_customer_id);
853       write_debug_and_log('- Customer Site Id: '||p_site_use_id);
854       write_debug_and_log('- Receipt Method Id: '||p_receipt_method_id);
855       write_debug_and_log('- Payment Schedule Id: '||p_payment_schedule_id);
856       write_debug_and_log('ERROR =>'|| SQLERRM);
857 
858       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
859       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
860       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
861       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
862       FND_MSG_PUB.ADD;
863 
864 END get_payment_information;
865 
866 /*========================================================================
867  | PUBLIC procedure update_expiration_date
868  |
869  | DESCRIPTION
870  |      Updates credit card expiration date
871  |      ----------------------------------------
872  |
873  | PSEUDO CODE/LOGIC
874  |
875  | PARAMETERS
876  |
877  |      p_bank_account_id         Credit Card bank account id
878  |      p_expiration_date	  New expiration date
879  |
880  | KNOWN ISSUES
881  |
882  |
883  |
884  | NOTES
885  |
886  |
887  |
888  | MODIFICATION HISTORY
889  | Date                  Author            Description of Changes
890  | 10-FEB-2001           O Steinmeier      Created
891  |
892  *=======================================================================*/
893 PROCEDURE update_expiration_date( p_bank_account_id     IN  NUMBER,
894                                   p_expiration_date     IN  DATE,
895                                   p_payment_instrument  IN VARCHAR2,
896                                   p_branch_id			IN iby_ext_bank_accounts.BRANCH_ID%TYPE,
897                                   p_bank_id			    IN iby_ext_bank_accounts.BANK_ID%TYPE,
898                                   p_bank_account_num	IN iby_ext_bank_accounts.BANK_ACCOUNT_NUM%TYPE,
899                                   p_currency			IN iby_ext_bank_accounts.CURRENCY_CODE%TYPE,
900                                   p_object_version_number IN iby_ext_bank_accounts.OBJECT_VERSION_NUMBER%TYPE,
901 				  x_return_status       OUT NOCOPY VARCHAR,
902 				  x_msg_count           OUT NOCOPY NUMBER,
903 				  x_msg_data            OUT NOCOPY VARCHAR2) IS
904 
905    l_create_credit_card		IBY_FNDCPT_SETUP_PUB.CreditCard_rec_type;
906    l_ext_bank_acct_rec      IBY_EXT_BANKACCT_PUB.ExtBankAcct_rec_type;
907    l_result_rec			IBY_FNDCPT_COMMON_PUB.Result_rec_type;
908    l_procedure_name		VARCHAR2(30);
909    l_acct_holder_name   	iby_ext_bank_accounts.BANK_ACCOUNT_NAME%TYPE;
910    l_acct_type          	iby_ext_bank_accounts.BANK_ACCOUNT_TYPE%TYPE;
911    l_start_date         	DATE;
912 BEGIN
913 
914 l_procedure_name		     := '.update_expiration_date';
915 
916 IF p_payment_instrument = 'CREDIT_CARD' THEN
917 
918         WRITE_DEBUG_AND_LOG('In CC expiration date update');
919         l_create_credit_card.card_id         := p_bank_account_id ;
920         l_create_credit_card.expiration_date := p_expiration_date;
921 
922         IBY_FNDCPT_SETUP_PUB.update_card(
923 	        p_api_version      => 1.0,
924 	        p_init_msg_list    => FND_API.G_TRUE,
925 	        p_commit           => FND_API.G_FALSE,
926 	        x_return_status    => x_return_status,
927 	        x_msg_count        => x_msg_count,
928 	        x_msg_data         => x_msg_data,
929 	        p_card_instrument  => l_create_credit_card,
930 	        x_response         => l_result_rec);
931 
932 
933    IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
934       if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
935 	      fnd_log.string(fnd_log.LEVEL_STATEMENT,
936                       G_PKG_NAME||l_procedure_name,
937                       'ERROR IN UPDATING CREDIT CARD');
938           fnd_log.string(fnd_log.LEVEL_STATEMENT,
939                       G_PKG_NAME||l_procedure_name,l_result_rec.result_code);
940       end if;
941       x_msg_data      := l_result_rec.result_code;
942       x_return_status := FND_API.G_RET_STS_ERROR;
943       write_error_messages(x_msg_data, x_msg_count);
944     END IF;
945 ELSE
946 
947         WRITE_DEBUG_AND_LOG('In BA expiration date update');
948 
949         SELECT BANK_ACCOUNT_NAME, BANK_ACCOUNT_TYPE, START_DATE INTO l_acct_holder_name, l_acct_type, l_start_date
950 	  FROM IBY_EXT_BANK_ACCOUNTS WHERE EXT_BANK_ACCOUNT_ID = p_bank_account_id AND BRANCH_ID = p_branch_id AND BANK_ID = p_bank_id
951 	  AND BANK_ACCOUNT_NUM = p_bank_account_num AND CURRENCY_CODE = p_currency AND OBJECT_VERSION_NUMBER = p_object_version_number;
952         l_ext_bank_acct_rec.branch_id               := p_branch_id;
953         l_ext_bank_acct_rec.bank_id                 := p_bank_id;
954         l_ext_bank_acct_rec.bank_account_num        := p_bank_account_num;
955         l_ext_bank_acct_rec.currency                := p_currency;
956         l_ext_bank_acct_rec.object_version_number   := p_object_version_number;
957         l_ext_bank_acct_rec.bank_account_id         := p_bank_account_id;
958         l_ext_bank_acct_rec.end_date                := p_expiration_date;
959 	  l_ext_bank_acct_rec.bank_account_name       := l_acct_holder_name;
960         l_ext_bank_acct_rec.acct_type               := l_acct_type;
961         l_ext_bank_acct_rec.start_date              := l_start_date;
962 
963         WRITE_DEBUG_AND_LOG('p_branch_id'||p_branch_id||'p_bank_id'||p_bank_id||
964                             'p_bank_account_num ' || p_bank_account_num ||
965                             'p_object_version_number ' || p_object_version_number ||
966                             'p_bank_account_id ' || p_bank_account_id ||
967                             'p_currency ' || p_currency||' l_acct_holder_name '||l_acct_holder_name||
968 				    'l_acct_type '||l_acct_type||' l_start_date '||l_start_date);
969 
970         IBY_EXT_BANKACCT_PUB.update_ext_bank_acct(
971                 p_api_version       => 1.0,
972                 p_init_msg_list     => FND_API.G_TRUE,
973                 p_ext_bank_acct_rec => l_ext_bank_acct_rec,
974                 x_return_status     => x_return_status,
975                 x_msg_count         => x_msg_count,
976                 x_msg_data          => x_msg_data,
977                 x_response          => l_result_rec);
978 
979 
980    IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
981       if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
982 	      fnd_log.string(fnd_log.LEVEL_STATEMENT,
983                       G_PKG_NAME||l_procedure_name,
984                       'ERROR IN UPDATING BANK ACCOUNT');
985           fnd_log.string(fnd_log.LEVEL_STATEMENT,
986                       G_PKG_NAME||l_procedure_name,x_msg_data);
987       end if;
988       x_return_status := FND_API.G_RET_STS_ERROR;
989       write_error_messages(x_msg_data, x_msg_count);
990     END IF;
991 END IF;
992 
993 
994 EXCEPTION
995 WHEN OTHERS THEN
996       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
997       write_debug_and_log('- Card Id: '||p_bank_account_id);
998       write_debug_and_log('- Expiration Date: '||p_expiration_date);
999       write_debug_and_log('ERROR =>'|| SQLERRM);
1000 
1001       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
1002       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
1003       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1004 
1005       FND_MSG_PUB.ADD;
1006 
1007 END;
1008 /*========================================================================
1009  | PUBLIC function allow_payment
1010  |
1011  | DESCRIPTION
1012  |      Determines if payment schedule can be paid:
1013  |
1014  |   It will return TRUE if
1015  |
1016  |   - payment button is enabled via function security
1017  |     (need to define function)
1018  |   - the remaining balance of the payment schedule is > 0
1019  |   - a payment method has been defined in AR_SYSTEM_PARAMETERS
1020  |     for credit card payments
1021  |   - a bank account assignment in the currency of the invoice
1022  |     exists and is active.
1023  |
1024  |   Use this function to enable or disable the "Pay" button on
1025  |   the invoice and invoice activities pages.
1026  |
1027  |
1028  |      ----------------------------------------
1029  |
1030  | PSEUDO CODE/LOGIC
1031  |
1032  | PARAMETERS
1033  |
1034  |      p_payment_schedule_id     Payment Schedule to be paid
1035  |
1036  | KNOWN ISSUES
1037  |
1038  |
1039  |
1040  | NOTES
1041  |
1042  |
1043  |
1044  | MODIFICATION HISTORY
1045  | Date                  Author            Description of Changes
1046  | 13-FEB-2001           O Steinmeier      Created
1047  |
1048  *=======================================================================*/
1049 
1050 
1051 FUNCTION allow_payment(p_payment_schedule_id IN NUMBER, p_customer_id IN NUMBER , p_customer_site_id IN NUMBER)  RETURN BOOLEAN IS
1052 
1053   l_ps_balance    NUMBER;
1054   l_bank_account_method   NUMBER;
1055   l_credit_card_method    NUMBER; /* J Rautiainen ACH Implementation */
1056   l_currency_code ar_payment_schedules.invoice_currency_code%type;
1057   l_class        ar_payment_schedules.class%TYPE;
1058   l_creation_status ar_receipt_classes.creation_status%TYPE;
1059 
1060 BEGIN
1061 
1062   -- check that function security is allowing access to payment button
1063 
1064   IF NOT fnd_function.test('ARW_PAY_INVOICE') THEN
1065     RETURN FALSE;
1066   END IF;
1067 
1068   -- check trx type and balance: trx type must be debit item, balance > 0
1069 
1070   SELECT amount_due_remaining, class, invoice_currency_code
1071   INTO   l_ps_balance, l_class, l_currency_code
1072   FROM   ar_payment_schedules
1073   WHERE  payment_schedule_id = p_payment_schedule_id;
1074   --Bug 4161986 - Pay Icon does not appear in the ChargeBack and its activities page. Added the class CB(Chargeback)
1075   IF l_ps_balance <= 0
1076      OR l_class NOT IN ('INV', 'DEP', 'GUAR', 'DM', 'CB') THEN
1077 
1078      RETURN FALSE;
1079 
1080   END IF;
1081 
1082   -- verify that method is set up
1083   l_credit_card_method := is_credit_card_payment_enabled(p_customer_id , p_customer_site_id , l_currency_code) ;
1084 
1085   -- Bug 3338276
1086   -- If one-time payment is enabled, bank account payment is not enabled;
1087   -- Hence, the check for valid bank account payment methods can be defaulted to 0.
1088   -- Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.save_payment_instrument_info
1089   IF NOT ARI_UTILITIES.save_payment_instrument_info(p_customer_id , p_customer_site_id) THEN
1090     l_bank_account_method := 0;
1091   ELSE
1092     l_bank_account_method := is_bank_acc_payment_enabled(p_customer_id , p_customer_site_id , l_currency_code);
1093   END IF;
1094 
1095   IF   l_bank_account_method  = 0
1096    AND l_credit_card_method = 0
1097   THEN
1098     RETURN FALSE;
1099 
1100   END IF;
1101 
1102   RETURN TRUE;
1103 
1104 END allow_payment;
1105 
1106 -- cover function on top of allow_payments to allow usage in SQL statements.
1107 
1108 FUNCTION payment_allowed(p_payment_schedule_id IN NUMBER,p_customer_id IN NUMBER , p_customer_site_id IN NUMBER) RETURN NUMBER IS
1109 BEGIN
1110   if allow_payment(p_payment_schedule_id , p_customer_id , p_customer_site_id ) then
1111      return 1;
1112   else
1113      return 0;
1114   end if;
1115 END payment_allowed;
1116 
1117 /*========================================================================
1118  | PUBLIC procedure get_default_payment_instrument
1119  |
1120  | DESCRIPTION
1121  |      Return payment instrument information if one can be defaulted for the user
1122  |      ----------------------------------------
1123  |
1124  | PSEUDO CODE/LOGIC
1125  |
1126  | PARAMETERS
1127  |      customer_id IN Customer Id to which credit cards are releated to
1128  |      customer_site_use_id IN Customer Site Use Id to which credit cards are releated to
1129  |	currency_code	IN	VARCHAR2
1130  |
1131  | RETURNS
1132  |      p_bank_account_num_masked Masked credit card number
1133  |      p_credit_card_type        Type of the credit card
1134  |      p_expiry_month            Credit card expiry month
1135  |      p_expiry_year             Credit card expiry year
1136  |      p_credit_card_expired     '1' if credit card has expired, '0' otherwise
1137  |      p_bank_account_id         Bank Account id of the credit card
1138  |
1139  | KNOWN ISSUES
1140  |
1141  | NOTES
1142  |
1143  | MODIFICATION HISTORY
1144  | Date                  Author            Description of Changes
1145  | 22-JAN-2001           J Rautiainen      Created
1146  | 20-May-2004		 hikumar	   Added currencyCode
1147  | 26-Oct-2004       vnb           Bug 3944029 - Correct payment instrument to be picked at customer account level
1148  | 23-Dec-2004       vnb           Bug 3928412 - RA_CUSTOMERS obsolete;removed reference to it
1149  *=======================================================================*/
1150 PROCEDURE get_default_payment_instrument(p_customer_id             IN  NUMBER,
1151                                          p_customer_site_use_id    IN  NUMBER DEFAULT NULL,
1152                                          p_currency_code	   IN  VARCHAR2,
1153 					 p_bank_account_num_masked OUT NOCOPY VARCHAR2,
1154                                          p_account_type            OUT NOCOPY VARCHAR2,
1155                                          p_expiry_month            OUT NOCOPY VARCHAR2,
1156                                          p_expiry_year             OUT NOCOPY VARCHAR2,
1157                                          p_credit_card_expired     OUT NOCOPY VARCHAR2,
1158                                          p_bank_account_id         OUT NOCOPY ce_bank_accounts.bank_account_id%TYPE,
1159                                          p_bank_branch_id          OUT NOCOPY ce_bank_accounts.bank_branch_id%TYPE,
1160                                          p_account_holder          OUT NOCOPY VARCHAR2,
1161                                          p_card_brand		   OUT NOCOPY VARCHAR2,
1162                                          p_cvv_code		   OUT NOCOPY VARCHAR2,
1163                                          p_conc_address		   OUT NOCOPY VARCHAR2,
1164                                          p_cc_bill_site_id  	   OUT NOCOPY NUMBER,
1165                                          p_instr_assignment_id	   OUT NOCOPY NUMBER,
1166                                          p_bank_party_id	   OUT NOCOPY NUMBER,
1167                                          p_branch_party_id	   OUT NOCOPY NUMBER,
1168                                          p_object_version_no	   OUT NOCOPY NUMBER
1169                                          ) IS
1170 
1171   cursor last_used_instr_cur  IS
1172               SELECT bank.masked_bank_account_num  bank_account_num_masked,
1173   bank.bank_account_type account_type,
1174   NULL expiry_month,
1175   NULL expiry_year,
1176   '0' credit_card_expired,
1177   u.instrument_id bank_account_id,
1178   bank.branch_id bank_branch_id,
1179   bank.bank_account_name account_holder,
1180   NULL cvv_code,
1181   NULL conc_address,
1182   NULL card_code,
1183   NULL party_site_id,
1184   u.instrument_payment_use_id instr_assignment_id,
1185   bank.bank_id bank_party_id,
1186   bank.branch_id branch_party_id,
1187   bank.object_version_number
1188 FROM hz_cust_accounts cust,
1189   hz_party_preferences pp1,
1190   iby_external_payers_all p,
1191   iby_pmt_instr_uses_all u,
1192   iby_ext_bank_accounts bank,
1193   hz_organization_profiles bapr,
1194   hz_organization_profiles brpr,
1195   iby_account_owners ow
1196 WHERE cust.cust_account_id = p_customer_id
1197  AND pp1.party_id = cust.party_id
1198  AND pp1.category = 'LAST_USED_PAYMENT_INSTRUMENT'
1199  AND pp1.preference_code = 'INSTRUMENT_ID'
1200  AND p.cust_account_id = p_customer_id
1201  AND p.party_id = cust.party_id
1202  AND (	(p.acct_site_use_id = p_customer_site_use_id) 	OR
1203 	(p.acct_site_use_id IS NULL  AND decode(p_customer_site_use_id,   -1,   NULL,   p_customer_site_use_id) IS NULL)  )
1204  AND u.ext_pmt_party_id = p.ext_payer_id
1205  AND u.instrument_type = 'BANKACCOUNT'
1206  AND u.payment_flow = 'FUNDS_CAPTURE'
1207  AND u.instrument_id = pp1.value_number
1208  AND pp1.value_number = bank.ext_bank_account_id(+)
1209  AND (  decode(bank.currency_code,   NULL,   'Y',   'N')='Y'  OR bank.currency_code = p_currency_code)
1210  AND bank.bank_id = bapr.party_id(+)
1211  AND bank.branch_id = brpr.party_id(+)
1212  AND TRUNC(sysdate) BETWEEN nvl(TRUNC(bapr.effective_start_date),   sysdate -1)  AND nvl(TRUNC(bapr.effective_end_date),   sysdate + 1)
1213  AND TRUNC(sysdate) BETWEEN nvl(TRUNC(brpr.effective_start_date),   sysdate -1)  AND nvl(TRUNC(brpr.effective_end_date),   sysdate + 1)
1214  AND bank.ext_bank_account_id = ow.ext_bank_account_id(+)
1215  AND ow.primary_flag(+) = 'Y'
1216  AND nvl(TRUNC(ow.end_date),   sysdate + 10) > TRUNC(sysdate)
1217 
1218 
1219 UNION ALL
1220 
1221 
1222 SELECT c.masked_cc_number bank_account_num_masked,
1223   decode(i.card_issuer_code,   NULL,   ccunk.meaning,   i.card_issuer_name) account_type,
1224   null expiry_month,
1225   null expiry_year,
1226   '0' credit_card_expired,
1227   u.instrument_id bank_account_id,
1228   1 bank_branch_id,
1229   nvl(c.chname,   hzcc.party_name) account_holder,
1230   NULL cvv_code,
1231   arp_addr_pkg.format_address(loc.address_style,   loc.address1,   loc.address2,   loc.address3,   loc.address4,   loc.city,   loc.county,   loc.state,   loc.province,   loc.postal_code,   terr.territory_short_name) conc_address,
1232   c.card_issuer_code card_code,
1233   psu.party_site_id,
1234   u.instrument_payment_use_id,
1235   NULL bank_party_id,
1236   NULL branch_party_id,
1237   NULL object_version_number
1238 FROM hz_cust_accounts cust,
1239   hz_party_preferences pp1,
1240   iby_external_payers_all p,
1241   iby_pmt_instr_uses_all u,
1242   iby_creditcard c,
1243   iby_creditcard_issuers_vl i,
1244   hz_parties hzcc,
1245   hz_party_site_uses psu,
1246   hz_party_sites hps,
1247   hz_locations loc,
1248   fnd_territories_vl terr,
1249   fnd_lookup_values_vl ccunk
1250 WHERE cust.cust_account_id = p_customer_id
1251  AND pp1.party_id = cust.party_id
1252  AND pp1.category = 'LAST_USED_PAYMENT_INSTRUMENT'
1253  AND pp1.preference_code = 'INSTRUMENT_ID'
1254  AND p.cust_account_id = p_customer_id
1255  AND p.party_id = cust.party_id
1256  AND (	(p.acct_site_use_id = p_customer_site_use_id)  	OR
1257 	(p.acct_site_use_id IS NULL  AND decode(p_customer_site_use_id,   -1,   NULL,   p_customer_site_use_id) IS NULL)  )
1258  AND u.ext_pmt_party_id = p.ext_payer_id
1259  AND u.instrument_type = 'CREDITCARD'
1260  AND u.payment_flow = 'FUNDS_CAPTURE'
1261  AND u.instrument_id = pp1.value_number
1262  AND u.instrument_id = c.instrid(+)
1263  AND nvl(c.inactive_date,   sysdate + 10) > sysdate
1264  AND c.card_issuer_code = i.card_issuer_code(+)
1265  AND c.card_owner_id = hzcc.party_id(+)
1266  AND c.addressid = psu.party_site_use_id(+)
1267  AND psu.party_site_id = hps.party_site_id(+)
1268  AND hps.location_id = loc.location_id(+)
1269  AND loc.country = terr.territory_code(+)
1270  AND ccunk.lookup_type = 'IBY_CARD_TYPES'
1271  AND ccunk.lookup_code = 'UNKNOWN';
1272 
1273 
1274  CURSOR bank_account_cur IS
1275 	SELECT
1276 		  u.instrument_type instrument_type,
1277 		  bank.masked_bank_account_num bank_account_num_masked,
1278 		  bank.bank_account_type account_type,
1279 		  null expiry_month,
1280 		  null expiry_year,
1281 		  '0' credit_card_expired,
1282 		  u.instrument_id bank_account_id,
1283 		  bank.branch_id bank_branch_id,
1284 		  bank.bank_account_name account_holder,
1285 		  null cvv_code,
1286 		  null conc_address,
1287 		  null card_code,
1288 		  null party_site_id,
1289 		  u.instrument_payment_use_id instr_assignment_id,
1290 		  bank.bank_id bank_party_id,
1291 		  bank.branch_id branch_party_id,
1292 		  bank.object_version_number
1293 	FROM
1294 		  hz_cust_accounts cust,
1295 		  iby_external_payers_all p,
1296 		  iby_pmt_instr_uses_all u,
1297 		  iby_ext_bank_accounts bank,
1298 		  hz_organization_profiles bapr,
1299 		  hz_organization_profiles brpr,
1300 		  iby_account_owners ow
1301 
1302 	WHERE
1303 		 cust.cust_account_id = p_customer_id
1304 		 AND p.cust_account_id = cust.cust_account_id
1305 		 AND p.party_id = cust.party_id
1306 		 AND (
1307 			(p.acct_site_use_id = p_customer_site_use_id)
1308 				OR
1309 			(p.acct_site_use_id IS NULL AND DECODE(p_customer_site_use_id, -1, NULL, p_customer_site_use_id) IS NULL)
1310 		    )
1311 		 AND u.ext_pmt_party_id = p.ext_payer_id
1312 		 AND u.instrument_type='BANKACCOUNT'
1313 		 AND u.payment_flow = 'FUNDS_CAPTURE'
1314 		 AND u.instrument_id = bank.ext_bank_account_id(+)
1315 		 AND ( decode(bank.currency_code,   NULL,   'Y',   'N')='Y' OR bank.currency_code = p_currency_code)
1316 		 AND bank.bank_id = bapr.party_id(+)
1317 		 AND bank.branch_id = brpr.party_id(+)
1318 		 AND TRUNC(sysdate) BETWEEN nvl(TRUNC(bapr.effective_start_date),   sysdate -1)  AND nvl(TRUNC(bapr.effective_end_date),   sysdate + 1)
1319 		 AND TRUNC(sysdate) BETWEEN nvl(TRUNC(brpr.effective_start_date),   sysdate -1)  AND nvl(TRUNC(brpr.effective_end_date),   sysdate + 1)
1320 		 AND bank.ext_bank_account_id = ow.ext_bank_account_id(+)
1321 		 AND ow.primary_flag(+) = 'Y'
1322 		 AND nvl(TRUNC(ow.end_date),   sysdate + 10) > TRUNC(sysdate);
1323 
1324  CURSOR credit_card_cur IS
1325 	SELECT
1326 		  u.instrument_type instrument_type,
1327 		  c.masked_cc_number bank_account_num_masked,
1328 		  decode(i.card_issuer_code, NULL, ccunk.meaning, i.card_issuer_name) account_type,
1329 		  null expiry_month,
1330 		  null expiry_year,
1331 		  '0' credit_card_expired,
1332 		  u.instrument_id bank_account_id,
1333 		  1 bank_branch_id,
1334 		  NVL(c.chname,hzcc.party_name) account_holder,
1335 		  NULL cvv_code,
1336 		  arp_addr_pkg.format_address(loc.address_style,   loc.address1,   loc.address2,   loc.address3,   loc.address4,   loc.city,   loc.county,   loc.state,   loc.province,   loc.postal_code,   terr.territory_short_name) conc_address,
1337 		  c.card_issuer_code card_code,
1338 		  psu.party_site_id,
1339 		  u.instrument_payment_use_id instr_assignment_id,
1340 		  NULL bank_party_id,
1341 		  NULL branch_party_id,
1342 		  NULL object_version_number
1343 	FROM
1344 		  fnd_lookup_values_vl ccunk,
1345 		  iby_creditcard c,
1346 		  iby_creditcard_issuers_vl i,
1347 		  iby_external_payers_all p,
1348 		  iby_pmt_instr_uses_all u,
1349 		  hz_parties hzcc,
1350 		  hz_cust_accounts cust,
1351 		  hz_party_site_uses psu,
1352 		  hz_party_sites hps,
1353 		  hz_locations loc,
1354 		  fnd_territories_vl terr
1355 	WHERE
1356 		 cust.cust_account_id = p_customer_id
1357 		 AND p.cust_account_id = cust.cust_account_id
1358 		 AND p.party_id = cust.party_id
1359 		 AND (
1360 			(p.acct_site_use_id = p_customer_site_use_id)
1361 				OR
1362 			(p.acct_site_use_id IS NULL AND DECODE(p_customer_site_use_id, -1, NULL, p_customer_site_use_id) IS NULL)
1363 		     )
1364 		 AND u.ext_pmt_party_id = p.ext_payer_id
1365 		 AND u.instrument_type = 'CREDITCARD'
1366 		 AND u.payment_flow = 'FUNDS_CAPTURE'
1367 		 AND u.instrument_id = c.instrid(+)
1368 		 AND nvl(c.inactive_date,   sysdate + 10) > sysdate
1369 		 AND c.card_issuer_code = i.card_issuer_code(+)
1370 		 AND c.card_owner_id = hzcc.party_id(+)
1371 		 AND c.addressid = psu.party_site_use_id(+)
1372 		 AND psu.party_site_id = hps.party_site_id(+)
1373 		 AND hps.location_id = loc.location_id(+)
1374 		 AND loc.country = terr.territory_code(+)
1375 		 AND ccunk.lookup_type = 'IBY_CARD_TYPES'
1376 		 AND ccunk.lookup_code = 'UNKNOWN';
1377 
1378 
1379   bank_account_rec     bank_account_cur%ROWTYPE;
1380   credit_card_rec      credit_card_cur%ROWTYPE;
1381   last_used_instr_rec  last_used_instr_cur%ROWTYPE;
1382 
1383 
1384   l_ba_count           NUMBER := 0;
1385   l_cc_count           NUMBER := 0;
1386   l_result             ce_bank_accounts.bank_account_num%TYPE;
1387   l_payment_instrument VARCHAR2(100);
1388 
1389   x_return_status     VARCHAR2(100);
1390   x_cvv_use           VARCHAR2(100);
1391   x_billing_addr_use  VARCHAR2(100);
1392   x_msg_count         NUMBER;
1393   x_msg_data          VARCHAR2(100);
1394 
1395 BEGIN
1396 
1397     get_payment_channel_attribs
1398     (
1399       p_channel_code => 'CREDIT_CARD',
1400       x_return_status  => x_return_status,
1401       x_cvv_use => x_cvv_use,
1402       x_billing_addr_use => x_billing_addr_use,
1403       x_msg_count => x_msg_count,
1404       x_msg_data => x_msg_data
1405      );
1406 
1407 /*
1408 If there are multiple BA and only 1 CC, we return the CC details
1409 If there is 1 BA and multiple CC, we return the BA details
1410 If there is 1 BA, 1CC we return the BA details
1411 
1412 Return NULL values in the following cases:
1413 1)If there are more than one BA and more than one CC
1414 2)If no saved instrument exists
1415 3)If there's only one saved instrument and it doesn't have address
1416 */
1417 
1418    OPEN last_used_instr_cur;
1419    FETCH last_used_instr_cur INTO last_used_instr_rec;
1420 
1421    IF last_used_instr_cur%FOUND THEN
1422 	  --If there's a last used instrument, return the address and other details.
1423 	  --But, if that instrument doesn't have a BilltositeID associated(i.e., no bill to address), we return empty values
1424 
1425      CLOSE last_used_instr_cur;
1426 
1427 -- bank_branch_id will be always 1  for CC , --  bug 7712779
1428 
1429 if(last_used_instr_rec.bank_branch_id = 1) then
1430     if(ar_irec_payments.is_credit_card_payment_enabled(p_customer_id , p_customer_site_use_id , p_currency_code) = 1) then
1431      p_bank_account_num_masked := last_used_instr_rec.bank_account_num_masked;
1432      p_credit_card_expired     := last_used_instr_rec.credit_card_expired;
1433      p_account_type            := last_used_instr_rec.account_type;
1434      p_expiry_month            := last_used_instr_rec.expiry_month;
1435      p_expiry_year             := last_used_instr_rec.expiry_year;
1436      p_bank_account_id         := last_used_instr_rec.bank_account_id;
1437      p_bank_branch_id          := last_used_instr_rec.bank_branch_id;
1438      p_account_holder          := last_used_instr_rec.account_holder;
1439      p_cvv_code		       := last_used_instr_rec.cvv_code;
1440      p_card_brand	       := last_used_instr_rec.card_code;
1441      p_conc_address	       := last_used_instr_rec.conc_address;
1442      p_cc_bill_site_id	       := last_used_instr_rec.party_site_id;
1443      p_instr_assignment_id     := last_used_instr_rec.instr_assignment_id;
1444      p_bank_party_id	       := last_used_instr_rec.bank_party_id;
1445      p_branch_party_id	       := last_used_instr_rec.branch_party_id;
1446      p_object_version_no       := last_used_instr_rec.object_version_number;
1447    end if;
1448 
1449    else
1450    -- bug 7712779
1451 
1452     if(ar_irec_payments.is_bank_acc_payment_enabled(p_customer_id , p_customer_site_use_id , p_currency_code)=1) then
1453      p_bank_account_num_masked := last_used_instr_rec.bank_account_num_masked;
1454      p_credit_card_expired     := last_used_instr_rec.credit_card_expired;
1455      p_account_type            := last_used_instr_rec.account_type;
1456      p_expiry_month            := last_used_instr_rec.expiry_month;
1457      p_expiry_year             := last_used_instr_rec.expiry_year;
1458      p_bank_account_id         := last_used_instr_rec.bank_account_id;
1459      p_bank_branch_id          := last_used_instr_rec.bank_branch_id;
1460      p_account_holder          := last_used_instr_rec.account_holder;
1461      p_cvv_code		       := last_used_instr_rec.cvv_code;
1462      p_card_brand	       := last_used_instr_rec.card_code;
1463      p_conc_address	       := last_used_instr_rec.conc_address;
1464      p_cc_bill_site_id	       := last_used_instr_rec.party_site_id;
1465      p_instr_assignment_id     := last_used_instr_rec.instr_assignment_id;
1466      p_bank_party_id	       := last_used_instr_rec.bank_party_id;
1467      p_branch_party_id	       := last_used_instr_rec.branch_party_id;
1468      p_object_version_no       := last_used_instr_rec.object_version_number;
1469     end if;
1470 
1471   end if;
1472 
1473 
1474      /* Bug 4744886 - When last used payment instrument is created without Address
1475         and if profile value now requires Address, then this procedure will return
1476         no default instrument found, so that it would be taken to Adv Pmt Page
1477 
1478 	p_bank_branch_id is 1 only for Credit Cards
1479       */
1480 
1481 
1482     if(p_bank_branch_id = 1 and p_cc_bill_site_id is NULL
1483 	     and (x_billing_addr_use ='REQUIRED') ) then
1484             p_bank_account_num_masked := '';
1485             p_account_type            := '';
1486             p_expiry_month            := '';
1487             p_expiry_year             := '';
1488             p_bank_account_id         := TO_NUMBER(NULL);
1489             p_bank_branch_id          := TO_NUMBER(NULL);
1490             p_credit_card_expired     := '';
1491             p_account_holder          := '';
1492             p_card_brand	      := '';
1493             p_cvv_code		      := '';
1494             p_conc_address	      := '';
1495             p_cc_bill_site_id	      := TO_NUMBER(NULL);
1496             p_instr_assignment_id     := TO_NUMBER(NULL);
1497             p_bank_party_id	      := TO_NUMBER(NULL);
1498             p_branch_party_id	      := TO_NUMBER(NULL);
1499             p_object_version_no	      := TO_NUMBER(NULL);
1500      END IF;
1501 
1502 
1503    ELSE
1504      --If there's NO last used instrument
1505 
1506      CLOSE last_used_instr_cur;
1507 
1508      FOR bank_account_rec IN bank_account_cur LOOP
1509 
1510               --  bug 7712779
1511 
1512      	       if(ar_irec_payments.is_bank_acc_payment_enabled(p_customer_id , p_customer_site_use_id , p_currency_code) = 0) then
1513                     EXIT;
1514 	       end if;
1515 
1516 		--If there are any BA, in the first iteration read those values.
1517 		--From 2nd iteration, maintain a count of the BA and CC existing
1518 
1519 	       IF (l_ba_count = 0) THEN
1520 		     l_payment_instrument      :='BANKACCOUNT';
1521 		     p_bank_account_num_masked := bank_account_rec.bank_account_num_masked;
1522 		     p_credit_card_expired     := bank_account_rec.credit_card_expired;
1523 		     p_account_type            := bank_account_rec.account_type;
1524 		     p_expiry_month            := bank_account_rec.expiry_month;
1525 		     p_expiry_year             := bank_account_rec.expiry_year;
1526 		     p_bank_account_id         := bank_account_rec.bank_account_id;
1527 		     p_bank_branch_id          := bank_account_rec.bank_branch_id;
1528 		     p_account_holder          := bank_account_rec.account_holder;
1529 		     p_card_brand	       := '';
1530 		     p_cvv_code		       := '';
1531 		     p_conc_address	       := '';
1532 		     p_cc_bill_site_id	       := '';
1533 		     p_instr_assignment_id     := bank_account_rec.instr_assignment_id;
1534 		     p_bank_party_id	       := bank_account_rec.bank_party_id;
1535 		     p_branch_party_id	       := bank_account_rec.branch_party_id;
1536 		     p_object_version_no       := bank_account_rec.object_version_number;
1537 	       END IF;
1538 
1539 	       l_ba_count                := l_ba_count + 1;
1540 
1541 		IF(l_ba_count > 1) THEN
1542 	  	     EXIT;
1543 		END IF;
1544 
1545      END LOOP;
1546 
1547      FOR credit_card_rec IN credit_card_cur LOOP
1548 
1549           --  bug 7712779
1550 
1551      		if(ar_irec_payments.is_credit_card_payment_enabled(p_customer_id , p_customer_site_use_id , p_currency_code)=0) then
1552                       EXIT;
1553 		end if;
1554 
1555 	       IF(l_ba_count <>1 AND l_cc_count = 0) THEN
1556 		     l_payment_instrument      := 'CREDITCARD';
1557 		     p_bank_account_num_masked := bank_account_rec.bank_account_num_masked;
1558 		     p_credit_card_expired     := bank_account_rec.credit_card_expired;
1559 		     p_account_type            := bank_account_rec.account_type;
1560 		     p_expiry_month            := bank_account_rec.expiry_month;
1561 		     p_expiry_year             := bank_account_rec.expiry_year;
1562 		     p_bank_account_id         := bank_account_rec.bank_account_id;
1563 		     p_bank_branch_id          := bank_account_rec.bank_branch_id;
1564 		     p_account_holder          := bank_account_rec.account_holder;
1565 		     p_card_brand	       := bank_account_rec.card_code;
1566 		     p_cvv_code		       := bank_account_rec.cvv_code;
1567 		     p_conc_address	       := bank_account_rec.conc_address;
1568 		     p_cc_bill_site_id	       := bank_account_rec.party_site_id;
1569 		     p_instr_assignment_id     := bank_account_rec.instr_assignment_id;
1570 		     p_bank_party_id	       := '';
1571 		     p_branch_party_id	       := '';
1572 		     p_object_version_no       := '';
1573 		END IF;
1574 
1575 		l_cc_count                := l_cc_count + 1;
1576 
1577 		IF(l_cc_count > 1) THEN
1578 			EXIT;
1579 		END IF;
1580      END LOOP;
1581 
1582 
1583      IF (   (l_payment_instrument = 'BANKACCOUNT'  AND l_ba_count > 1)
1584 	 OR (l_payment_instrument = 'CREDITCARD'   AND l_cc_count > 1)
1585 	 OR (l_payment_instrument IS NULL)
1586 	 OR (p_bank_branch_id = 1 and p_cc_bill_site_id is NULL
1587 	     and x_billing_addr_use ='REQUIRED')
1588 	) THEN
1589        p_bank_account_num_masked := '';
1590        p_account_type            := '';
1591        p_expiry_month            := '';
1592        p_expiry_year             := '';
1593        p_bank_account_id         := TO_NUMBER(NULL);
1594        p_bank_branch_id          := TO_NUMBER(NULL);
1595        p_credit_card_expired     := '';
1596        p_account_holder          := '';
1597        p_card_brand		 := '';
1598        p_cvv_code		 := '';
1599        p_conc_address	         := '';
1600        p_cc_bill_site_id	 := TO_NUMBER(NULL);
1601        p_instr_assignment_id     := TO_NUMBER(NULL);
1602        p_bank_party_id	         := '';
1603        p_branch_party_id	 := '';
1604        p_object_version_no       := '';
1605      END IF;
1606 
1607    END IF;
1608 
1609 END get_default_payment_instrument;
1610 
1611 
1612 
1613 
1614 
1615 
1616 /*========================================================================
1617  | PUBLIC function is_credit_card_expired
1618  |
1619  | DESCRIPTION
1620  |      Determines if a given credit card expiration date has passed.
1621  |      ----------------------------------------
1622  |
1623  | PSEUDO CODE/LOGIC
1624  |      This function compares given month and year in the given parameter
1625  |      to the month and year of the current date.
1626  |
1627  | PARAMETERS
1628  |      p_expiration_date   IN   Credit card expiration date
1629  |
1630  | RETURNS
1631  |      1     if credit card has expired
1632  |      0     if credit card has not expired
1633  |
1634  | KNOWN ISSUES
1635  |
1636  | NOTES
1637  |
1638  | MODIFICATION HISTORY
1639  | Date                  Author            Description of Changes
1640  | 21-Feb-2001           Jani Rautiainen   Created
1641  |
1642  *=======================================================================*/
1643 FUNCTION is_credit_card_expired(  p_expiration_date IN  DATE ) RETURN NUMBER IS
1644 
1645   CURSOR current_date_cur IS
1646     select to_char(to_number(to_char(sysdate,'MM'))) current_month,
1647            to_char(sysdate,'YYYY') current_year
1648     from dual;
1649 
1650   current_date_rec     current_date_cur%ROWTYPE;
1651 
1652 BEGIN
1653 
1654   OPEN current_date_cur;
1655   FETCH current_date_cur INTO current_date_rec;
1656   CLOSE current_date_cur;
1657 
1658   IF to_number(to_char(p_expiration_date,'YYYY')) < to_number(current_date_rec.current_year)
1659      OR (to_number(to_char(p_expiration_date,'YYYY')) = to_number(current_date_rec.current_year)
1660          AND  to_number(to_char(p_expiration_date,'MM')) < to_number(current_date_rec.current_month)) THEN
1661      return 1; --TRUE;
1662   else
1663      return 0; --FALSE
1664   end if;
1665 
1666 END is_credit_card_expired;
1667 
1668 /*========================================================================
1669  | PUBLIC procedure store_last_used_ba
1670  |
1671  | DESCRIPTION
1672  |      Stores the last used bank account
1673  |
1674  | PSEUDO CODE/LOGIC
1675  |
1676  | PARAMETERS
1677  |      p_customer_id      IN  NUMBER
1678  |      p_bank_account_id  IN  NUMBER
1679  |	p_instr_type	   IN  VARCHAR2 DEFAULT 'BA'
1680  |
1681  | RETURNS
1682  |      p_status	   OUT NOCOPY varchar2
1683  |
1684  | KNOWN ISSUES
1685  |
1686  | NOTES
1687  |
1688  | MODIFICATION HISTORY
1689  | Date                  Author            Description of Changes
1690  | 09-May-2001           J Rautiainen      Created
1691  | 26-Oct-2005	 	 rsinthre          Bug 4673563 - Error in updating last used instrument
1692  *=======================================================================*/
1693 PROCEDURE store_last_used_ba(p_customer_id     IN  NUMBER,
1694                              p_bank_account_id IN  NUMBER,
1695                              p_instr_type      IN  VARCHAR2 DEFAULT 'BA',
1696                              p_status          OUT NOCOPY VARCHAR2) IS
1697   l_msg_count             NUMBER;
1698   l_object_version_number NUMBER;
1699   l_msg_data              VARCHAR(2000);
1700 
1701   CURSOR customer_party_cur IS
1702     SELECT party_id
1703     FROM   hz_cust_accounts
1704     WHERE  cust_account_id = p_customer_id;
1705 
1706         CURSOR object_version_cur(p_party_id IN NUMBER, p_preference_code IN VARCHAR2) IS
1707            SELECT party_preference_id, object_version_number
1708         FROM   hz_party_preferences
1709         WHERE  party_id = p_party_id
1710         AND    category = 'LAST_USED_PAYMENT_INSTRUMENT'
1711         AND    preference_code = p_preference_code;
1712 
1713        customer_party_rec customer_party_cur%ROWTYPE;
1714       object_version_rec object_version_cur%ROWTYPE;
1715 
1716  BEGIN
1717 
1718    OPEN customer_party_cur;
1719    FETCH customer_party_cur INTO customer_party_rec;
1720    CLOSE customer_party_cur;
1721 
1722       OPEN object_version_cur(customer_party_rec.party_id,'INSTRUMENT_TYPE') ;
1723    FETCH object_version_cur INTO object_version_rec;
1724    CLOSE object_version_cur;
1725 
1726   SAVEPOINT STORE_INST;
1727 
1728     HZ_PREFERENCE_PUB.Put(
1729        p_party_id                 => customer_party_rec.party_id
1730   , p_category                  => 'LAST_USED_PAYMENT_INSTRUMENT'
1731   , p_preference_code          => 'INSTRUMENT_TYPE'
1732   , p_value_varchar2           => p_instr_type
1733   , p_module                   => 'IRECEIVABLES'
1734   , p_additional_value1        => NULL
1735   , p_additional_value2        => NULL
1736   , p_additional_value3        => NULL
1737   , p_additional_value4        => NULL
1738   , p_additional_value5        => NULL
1739   , p_object_version_number    => object_version_rec.object_version_number
1740   , x_return_status            => p_status
1741   , x_msg_count                => l_msg_count
1742   , x_msg_data                 => l_msg_data);
1743 
1744    IF ( p_status <> FND_API.G_RET_STS_SUCCESS ) THEN
1745                  write_error_messages(l_msg_data, l_msg_count);
1746                   ROLLBACK TO STORE_INST;
1747                  RETURN;
1748           END IF;
1749 
1750     OPEN object_version_cur(customer_party_rec.party_id,'INSTRUMENT_ID') ;
1751      FETCH object_version_cur INTO object_version_rec;
1752      CLOSE object_version_cur;
1753 
1754     HZ_PREFERENCE_PUB.Put(
1755         p_party_id                 => customer_party_rec.party_id
1756     , p_category                  => 'LAST_USED_PAYMENT_INSTRUMENT'
1757     , p_preference_code          => 'INSTRUMENT_ID'
1758     , p_value_number             => p_bank_account_id
1759     , p_module                   => 'IRECEIVABLES'
1760     , p_additional_value1        => NULL
1761     , p_additional_value2        => NULL
1762     , p_additional_value3        => NULL
1763     , p_additional_value4        => NULL
1764     , p_additional_value5        => NULL
1765     , p_object_version_number    => object_version_rec.object_version_number
1766     , x_return_status            => p_status
1767     , x_msg_count                => l_msg_count
1768     , x_msg_data                 => l_msg_data);
1769 
1770      IF ( p_status <> FND_API.G_RET_STS_SUCCESS ) THEN
1771                    write_error_messages(l_msg_data, l_msg_count);
1772                    ROLLBACK TO STORE_INST;
1773                    RETURN;
1774             END IF;
1775      --If payment process goes through, the transaction will be committed irrespective of
1776      --the result of this procedure. If the record is stored successfully in hz party preference, commit
1777      COMMIT;
1778 
1779 
1780      END store_last_used_ba;
1781 
1782 /*========================================================================
1783  | PUBLIC function is_bank_account_duplicate
1784  |
1785  | DESCRIPTION
1786  |      Checks whether given bank account number already exists
1787  |
1788  | PSEUDO CODE/LOGIC
1789  |
1790  | PARAMETERS
1791  |      p_bank_account_number IN  VARCHAR2
1792  |      p_routing_number      IN  VARCHAR2
1793  |      p_account_holder_name IN  VARCHAR2
1794  |
1795  | RETURNS
1796  |      Return Value: 0 if given bank account number does not exist.
1797  |                    1 if given bank account number already exists.
1798  |
1799  | KNOWN ISSUES
1800  |
1801  | NOTES
1802  |
1803  | MODIFICATION HISTORY
1804  | Date                  Author            Description of Changes
1805  | 01-Aug-2001           J Rautiainen      Created
1806  |
1807  | 15-Apr-2002           AMMISHRA          Bug:2210677 , Passed an extra
1808  |                                         parameter p_account_holder_name
1809  *=======================================================================*/
1810 FUNCTION is_bank_account_duplicate(p_bank_account_number IN  VARCHAR2,
1811                         p_routing_number      IN  VARCHAR2 DEFAULT NULL,
1812                         p_account_holder_name IN VARCHAR2) RETURN NUMBER IS
1813 
1814   CURSOR cc_cur(instrument_id iby_creditcard.instrid%TYPE)  is
1815          SELECT  count(1) ca_exists
1816 	 FROM    IBY_FNDCPT_PAYER_ASSGN_INSTR_V IBY
1817 	 WHERE   IBY.instrument_id = instrument_id
1818 	 AND     IBY.CARD_HOLDER_NAME <> p_account_holder_name;
1819 
1820   CURSOR ba_cur IS
1821     SELECT count(1) ba_exists
1822     FROM   iby_ext_bank_accounts_v ba
1823     WHERE  ba.branch_number       = p_routing_number
1824     AND    ba.bank_account_number = p_bank_account_number
1825     AND    ROWNUM = 1
1826     AND    ba.bank_account_name <> p_account_holder_name;
1827 
1828    ba_rec ba_cur%ROWTYPE;
1829    cc_rec cc_cur%ROWTYPE;
1830 
1831    l_create_credit_card		IBY_FNDCPT_SETUP_PUB.CreditCard_rec_type;
1832    l_result_rec			IBY_FNDCPT_COMMON_PUB.Result_rec_type;
1833    l_procedure_name		VARCHAR2(30);
1834    l_return_status		VARCHAR2(2);
1835    l_msg_count			NUMBER;
1836    l_msg_data			VARCHAR2(2000);
1837 BEGIN
1838   l_procedure_name := '.is_bank_account_duplicate';
1839 
1840   IF p_routing_number IS NULL THEN
1841 
1842 	   IBY_FNDCPT_SETUP_PUB.Card_Exists(
1843 		 p_api_version      => 1.0,
1844 		 p_init_msg_list    => FND_API.G_FALSE,
1845 		 x_return_status    => l_return_status,
1846 		 x_msg_count        => l_msg_count,
1847 		 x_msg_data         => l_msg_data,
1848 		 p_owner_id         => null,
1849 		 p_card_number      => p_bank_account_number,
1850 		 x_card_instrument  => l_create_credit_card,
1851 		 x_response         => l_result_rec);
1852 
1853 	  IF ( l_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
1854 	      -- no card exists
1855 		   return 0;
1856 	  ELSE
1857 	       OPEN  cc_cur(l_create_credit_card.card_id);
1858 	       FETCH cc_cur into cc_rec;
1859 	       CLOSE cc_cur;
1860 
1861 	       if cc_rec.ca_exists = 0 then
1862 		       return 0;
1863 	       else
1864 		       return 1;
1865 	       end if;
1866 
1867 	  END IF;
1868 
1869   ELSE
1870 
1871     open ba_cur;
1872     fetch ba_cur into ba_rec;
1873     close ba_cur;
1874 
1875     if ba_rec.ba_exists = 0 then
1876        return 0;
1877     else
1878        return 1;
1879     end if;
1880 
1881   END IF;
1882 
1883 EXCEPTION
1884 
1885 WHEN OTHERS THEN
1886       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
1887       write_debug_and_log('- Account Number: '||p_bank_account_number);
1888       write_debug_and_log('- Holder Name: '||p_account_holder_name);
1889       write_debug_and_log('ERROR =>'|| SQLERRM);
1890 
1891       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
1892       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
1893       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1894 
1895       FND_MSG_PUB.ADD;
1896 
1897 END is_bank_account_duplicate;
1898 
1899 /*========================================================================
1900  | PUBLIC function is_bank_account_duplicate
1901  |
1902  | DESCRIPTION
1903  |      Checks whether given bank account number already exists
1904  |
1905  | PSEUDO CODE/LOGIC
1906  |
1907  | PARAMETERS
1908  |      p_bank_account_number IN  VARCHAR2
1909  |
1910  | RETURNS
1911  |      Return Value: 0 if given bank account number does not exist.
1912  |                    1 if given bank account number already exists.
1913  |
1914  | KNOWN ISSUES
1915  |
1916  | NOTES
1917  |
1918  | MODIFICATION HISTORY
1919  | Date                  Author            Description of Changes
1920  | 01-Aug-2001           J Rautiainen      Created
1921  |
1922  *=======================================================================*/
1923 FUNCTION is_credit_card_duplicate(p_bank_account_number IN  VARCHAR2,
1924 				  p_account_holder_name IN  VARCHAR2) RETURN NUMBER IS
1925 BEGIN
1926   return  is_bank_account_duplicate(p_bank_account_number => p_bank_account_number,
1927                                     p_routing_number      => NULL,
1928 			            p_account_holder_name => p_account_holder_name);
1929 END is_credit_card_duplicate;
1930 
1931 /*========================================================================
1932  | PUBLIC function get_iby_account_type
1933  |
1934  | DESCRIPTION
1935  |      Maps AP bank account type to a iPayment bank account type. If
1936  |      AP bank account type is not recognized, CHECKING is used.
1937  |
1938  | PSEUDO CODE/LOGIC
1939  |
1940  | PARAMETERS
1941  |      p_account_type      Account type from the ap table
1942  |
1943  | RETURNS
1944  |      iPayment bank account type
1945  |
1946  | KNOWN ISSUES
1947  |
1948  | NOTES
1949  |
1950  | MODIFICATION HISTORY
1951  | Date                  Author            Description of Changes
1952  | 28-Feb-2002           J Rautiainen      Created
1953  |
1954  *=======================================================================*/
1955 FUNCTION get_iby_account_type(p_account_type        IN VARCHAR2) RETURN VARCHAR2 IS
1956 
1957   CURSOR account_type_cur IS
1958     select LOOKUP_CODE
1959     from FND_LOOKUPS
1960     where LOOKUP_TYPE = 'IBY_BANKACCT_TYPES'
1961     and   LOOKUP_CODE = UPPER(p_account_type);
1962 
1963   account_type_rec account_type_cur%ROWTYPE;
1964 BEGIN
1965 
1966   OPEN  account_type_cur;
1967   FETCH account_type_cur INTO account_type_rec;
1968 
1969   IF account_type_cur%FOUND THEN
1970     CLOSE account_type_cur;
1971     RETURN account_type_rec.LOOKUP_CODE;
1972   ELSE
1973     CLOSE account_type_cur;
1974     RETURN 'CHECKING';
1975   END IF;
1976 
1977 END get_iby_account_type;
1978 
1979 /*===========================================================================+
1980  | PROCEDURE write_debug_and_log                                             |
1981  |    	                                                                     |
1982  | DESCRIPTION                                                               |
1983  |    Writes standard messages to standard debugging and to the log          |
1984  |                                                                           |
1985  | SCOPE - PUBLIC                                                            |
1986  |                                                                           |
1987  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1988  |    arp_util.debug                                                         |
1989  |                                                                           |
1990  | ARGUMENTS  : IN:  p_message - Message to be writted                       |
1991  |                                                                           |
1992  | RETURNS    : NONE                                                         |
1993  |                                                                           |
1994  | MODIFICATION HISTORY                                                      |
1995  |     28-Feb-2002  Jani Rautiainen      Created                             |
1996  |                                                                           |
1997  +===========================================================================*/
1998 PROCEDURE write_debug_and_log(p_message IN VARCHAR2) IS
1999 
2000 BEGIN
2001 
2002  /*------------------------------------------------+
2003   | Write the message to log and to the standard   |
2004   | debugging channel                              |
2005   +------------------------------------------------*/
2006   IF FND_GLOBAL.CONC_REQUEST_ID is not null THEN
2007 
2008    /*------------------------------------------------+
2009     | Only write to the log if call was made from    |
2010     | concurrent program.                            |
2011     +------------------------------------------------*/
2012     fnd_file.put_line(FND_FILE.LOG,p_message);
2013 
2014   END IF;
2015 
2016   IF (PG_DEBUG = 'Y') THEN
2017      arp_standard.debug('OIR'|| p_message);
2018   END IF;
2019 EXCEPTION
2020   WHEN others THEN
2021    /*-------------------------------------------------------+
2022     | Error writing to the log, nothing we can do about it. |
2023     | Error is not raised since API messages also contain   |
2024     | non fatal warnings. If a real exception happened it   |
2025     | is handled on the calling routine.                    |
2026     +-------------------------------------------------------*/
2027     NULL;
2028 
2029 END write_debug_and_log;
2030 
2031 /*===========================================================================+
2032  | PROCEDURE write_API_output                                                |
2033  |    	                                                                     |
2034  | DESCRIPTION                                                               |
2035  |    Writes API output to the concurrent program log. Messages from the     |
2036  |    API can contain warnings and errors                                    |
2037  |                                                                           |
2038  | SCOPE - PUBLIC                                                            |
2039  |                                                                           |
2040  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
2041  |    arp_util.debug                                                         |
2042  |                                                                           |
2043  | ARGUMENTS  : IN:  p_msg_count  - Number of messages from the API          |
2044  |                   p_msg_data   - Actual messages from the API             |
2045  |                                                                           |
2046  | RETURNS    : NONE                                                         |
2047  |                                                                           |
2048  | MODIFICATION HISTORY                                                      |
2049  |     28-Feb-2002  Jani Rautiainen      Created                             |
2050  |                                                                           |
2051  +===========================================================================*/
2052 PROCEDURE write_API_output(p_msg_count        IN NUMBER,
2053                            p_msg_data         IN VARCHAR2) IS
2054 
2055   l_msg_data       VARCHAR2(2000);
2056 BEGIN
2057 
2058     --Bug 3810143 - Ensure that the messages are picked up from the message
2059     --stack in any case.
2060     FOR l_count IN 1..p_msg_count LOOP
2061 
2062          l_msg_data := FND_MSG_PUB.Get(FND_MSG_PUB.G_NEXT,FND_API.G_FALSE);
2063          write_debug_and_log(to_char(l_count)||' : '||l_msg_data);
2064 
2065     END LOOP;
2066 
2067 EXCEPTION
2068   WHEN others THEN
2069    /*-------------------------------------------------------+
2070     | Error writing to the log, nothing we can do about it. |
2071     | Error is not raised since API messages also contain   |
2072     | non fatal warnings. If a real exception happened it   |
2073     | is handled on the calling routine.                    |
2074     +-------------------------------------------------------*/
2075     NULL;
2076 
2077 END write_API_output;
2078 
2079 /*========================================================================
2080  | PUBLIC store_last_used_cc
2081  |
2082  | DESCRIPTION
2083  |      Backward compatibility methods introduced for mobile account
2084  |      management.
2085  |      ----------------------------------------
2086  |
2087  | MODIFICATION HISTORY
2088  | Date                  Author            Description of Changes
2089  | 10-Mar-2002           J Rautiainen      Created
2090  | 26-Apr-2004           vnb               Added Customer Site as input parameter.
2091  |
2092  *=======================================================================*/
2093 
2094 PROCEDURE store_last_used_cc(p_customer_id     IN  NUMBER,
2095                              p_bank_account_id IN  NUMBER,
2096                              p_status          OUT NOCOPY VARCHAR2) IS
2097 
2098 BEGIN
2099 store_last_used_ba(p_customer_id     => p_customer_id,
2100                    p_bank_account_id => p_bank_account_id,
2101                    p_instr_type      => 'CC',
2102                    p_status          => p_status);
2103 
2104 
2105 END store_last_used_cc;
2106 
2107 
2108 /*============================================================
2109  | PUBLIC procedure create_invoice_pay_list
2110  |
2111  | DESCRIPTION
2112  |   Creates a list of transactions to be paid by the customer
2113  |   based on the list type. List type has the following values:
2114  |   OPEN_INVOICES
2115  | PSEUDO CODE/LOGIC
2116  |
2117  | PARAMETERS
2118  |   p_customer_id           IN    NUMBER
2119  |   p_currency_code         IN    VARCHAR2
2120  |   p_customer_site_use_id  IN    NUMBER DEFAULT NULL
2121  |   p_payment_schedule_id   IN    NUMBER DEFAULT NULL
2122  |   p_trx_type              IN    VARCHAR2 DEFAULT NULL
2123  |
2124  | KNOWN ISSUES
2125  |
2126  |
2127  |
2128  | NOTES
2129  |
2130  |
2131  |
2132  | MODIFICATION HISTORY
2133  | Date          Author       Description of Changes
2134  | 13-Jan-2003   krmenon      Created
2135  | 31-Dec-2004   vnb          Bug 4071551 - Removed redundant code
2136  | 20-Jan-2005   vnb          Bug 4117211 - Original discount amount column added for ease of resetting payment amounts
2137  | 08-Jul-2005	 rsinthre     Bug 4437225 - Disputed amount against invoice not displayed during payment
2138  +============================================================*/
2139 PROCEDURE create_invoice_pay_list ( p_customer_id           IN NUMBER,
2140                                     p_customer_site_use_id  IN NUMBER DEFAULT NULL,
2141                                     p_payment_schedule_id   IN NUMBER DEFAULT NULL,
2142                                     p_currency_code         IN VARCHAR2
2143                                   ) IS
2144 
2145   -- Cursor to fetch all the open invoices
2146   CURSOR open_invoice_list (p_customer_id NUMBER,
2147                             p_customer_site_use_id NUMBER,
2148                             p_payment_schedule_id NUMBER,
2149                             p_currency_code VARCHAR2) IS
2150   SELECT ps.CUSTOMER_ID,
2151            ps.CUSTOMER_SITE_USE_ID,   -- Bug # 3828358
2152            acct.ACCOUNT_NUMBER,
2153            ps.CUSTOMER_TRX_ID,
2154            ps.TRX_NUMBER,
2155            ps.TRX_DATE,
2156   	 ps.class,
2157            ps.DUE_DATE,
2158   	 ps.PAYMENT_SCHEDULE_ID,
2159            ps.STATUS,
2160            trm.name term_desc,
2161   	 ARPT_SQL_FUNC_UTIL.Get_Number_Of_Due_Dates(ps.term_id) number_of_installments,
2162   	 ps.terms_sequence_number,
2163   	 ps.amount_line_items_original line_amount,
2164   	 ps.tax_original tax_amount,
2165   	 ps.freight_original freight_amount,
2166   	 ps.receivables_charges_charged finance_charge,
2167   	 ps.INVOICE_CURRENCY_CODE,
2168   	 ps.AMOUNT_DUE_ORIGINAL,
2169   	 ps.AMOUNT_DUE_REMAINING,
2170   	 0 payment_amt,
2171   	 0 service_charge,
2172   	 0 discount_amount,
2173   	 TRUNC(SYSDATE) receipt_date,
2174   	 '' receipt_number,
2175            ct.PURCHASE_ORDER AS PO_NUMBER,
2176            NULL AS SO_NUMBER,
2177            ct.printing_option,
2178 
2179            ct.ATTRIBUTE_CATEGORY,
2180            ct.ATTRIBUTE1,
2181            ct.ATTRIBUTE2,
2182            ct.ATTRIBUTE3,
2183            ct.ATTRIBUTE4,
2184            ct.ATTRIBUTE5,
2185            ct.ATTRIBUTE6,
2186            ct.ATTRIBUTE7,
2187            ct.ATTRIBUTE8,
2188            ct.ATTRIBUTE9,
2189            ct.ATTRIBUTE10,
2190            ct.ATTRIBUTE11,
2191            ct.ATTRIBUTE12,
2192            ct.ATTRIBUTE13,
2193            ct.ATTRIBUTE14,
2194            ct.ATTRIBUTE15,
2195            ct.INTERFACE_HEADER_CONTEXT,
2196 	   ct.INTERFACE_HEADER_ATTRIBUTE1,
2197 	   ct.INTERFACE_HEADER_ATTRIBUTE2,
2198 	   ct.INTERFACE_HEADER_ATTRIBUTE3,
2199 	   ct.INTERFACE_HEADER_ATTRIBUTE4,
2200 	   ct.INTERFACE_HEADER_ATTRIBUTE5,
2201 	   ct.INTERFACE_HEADER_ATTRIBUTE6,
2202 	   ct.INTERFACE_HEADER_ATTRIBUTE7,
2203 	   ct.INTERFACE_HEADER_ATTRIBUTE8,
2204 	   ct.INTERFACE_HEADER_ATTRIBUTE9,
2205 	   ct.INTERFACE_HEADER_ATTRIBUTE10,
2206 	   ct.INTERFACE_HEADER_ATTRIBUTE11,
2207 	   ct.INTERFACE_HEADER_ATTRIBUTE12,
2208 	   ct.INTERFACE_HEADER_ATTRIBUTE13,
2209 	   ct.INTERFACE_HEADER_ATTRIBUTE14,
2210 	   ct.INTERFACE_HEADER_ATTRIBUTE15,
2211   	 sysdate LAST_UPDATE_DATE,
2212   	 0 LAST_UPDATED_BY,
2213   	 sysdate CREATION_DATE,
2214   	 0 CREATED_BY,
2215   	 0 LAST_UPDATE_LOGIN,
2216   	 0 APPLICATION_AMOUNT,
2217   	 0 CASH_RECEIPT_ID,
2218   	 0  ORIGINAL_DISCOUNT_AMT,
2219            ps.org_id,
2220   	 ct.PAYING_CUSTOMER_ID,
2221   	 ct.PAYING_SITE_USE_ID,
2222 ( decode( nvl(ps.AMOUNT_DUE_ORIGINAL,0),0,1,(ps.AMOUNT_DUE_ORIGINAL/abs(ps.AMOUNT_DUE_ORIGINAL)) ) *abs(nvl(ps.amount_in_dispute,0)) ) dispute_amt
2223   FROM AR_PAYMENT_SCHEDULES ps,
2224        RA_CUSTOMER_TRX ct,
2225        HZ_CUST_ACCOUNTS acct,
2226        RA_TERMS trm
2227   WHERE ps.CLASS IN ('INV', 'DM', 'CB', 'DEP')
2228   AND ps.customer_trx_id = ct.customer_trx_id
2229   AND acct.cust_account_id = ps.customer_id
2230   AND ps.status = 'OP'
2231   AND ps.term_id = trm.term_id(+)
2232   AND ( ps.payment_schedule_id = p_payment_schedule_id
2233   	OR   p_payment_schedule_id IS NULL)
2234 
2235 	 AND ps.customer_id = p_customer_id
2236 	 AND ps.customer_site_use_id = nvl(decode(p_customer_site_use_id, -1, null, p_customer_site_use_id), ps.customer_site_use_id)
2237 	 AND ps.invoice_currency_code = p_currency_code;
2238 
2239   l_query_period NUMBER(15);
2240   l_query_date   DATE;
2241   l_total_service_charge NUMBER;
2242   l_discount_amount NUMBER;
2243   l_rem_amt_rcpt    NUMBER;
2244   l_rem_amt_inv     NUMBER;
2245   l_grace_days_flag VARCHAR2(2);
2246 
2247   l_paying_cust_id  NUMBER(15);
2248   l_pay_for_cust_id NUMBER(15);
2249   l_pay_for_cust_site_id NUMBER(15);
2250   l_paying_cust_site_id  NUMBER(15);
2251   l_dispute_amount	NUMBER := 0;
2252 
2253   l_procedure_name  VARCHAR2(50);
2254   l_debug_info      VARCHAR2(200);
2255 
2256   TYPE t_open_invoice_list_rec
2257         IS TABLE OF open_invoice_list%ROWTYPE index by binary_integer ;
2258 
2259   l_open_invoice_list_rec  t_open_invoice_list_rec;
2260 
2261 
2262 BEGIN
2263   --Assign default values
2264   l_query_period         := -12;
2265   l_total_service_charge := 0;
2266   l_discount_amount      := 0;
2267   l_rem_amt_rcpt         := 0;
2268   l_rem_amt_inv          := 0;
2269   l_procedure_name       := '.create_invoice_pay_list';
2270 
2271   SAVEPOINT create_invoice_pay_list_sp;
2272 
2273   ----------------------------------------------------------------------------------------
2274   l_debug_info := 'Clear the transaction list for the active customer, site, currency';
2275   -----------------------------------------------------------------------------------------
2276   IF (PG_DEBUG = 'Y') THEN
2277      arp_standard.debug(l_debug_info);
2278   END IF;
2279 
2280   --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
2281   DELETE FROM AR_IREC_PAYMENT_LIST_GT
2282   WHERE CUSTOMER_ID        = p_customer_id
2283   AND CUSTOMER_SITE_USE_ID = nvl(p_customer_site_use_id, CUSTOMER_SITE_USE_ID)
2284   AND CURRENCY_CODE        = p_currency_code;
2285 
2286   ----------------------------------------------------------------------------------------
2287   l_debug_info := 'Fetch all the rows into the global temporary table';
2288   -----------------------------------------------------------------------------------------
2289   IF (PG_DEBUG = 'Y') THEN
2290      arp_standard.debug(l_debug_info);
2291   END IF;
2292 
2293   Open  open_invoice_list(p_customer_id,
2294                                p_customer_site_use_id,
2295                                p_payment_schedule_id,
2296                                p_currency_code );
2297   FETCH  open_invoice_list BULK COLLECT INTO l_open_invoice_list_rec;
2298     close open_invoice_list;
2299 
2300     --l_grace_days_flag := is_grace_days_enabled_wrapper();
2301     l_grace_days_flag := ARI_UTILITIES.is_discount_grace_days_enabled(p_customer_id,p_customer_site_use_id);
2302 
2303   FOR trx IN l_open_invoice_list_rec.first .. l_open_invoice_list_rec.last loop
2304 
2305      IF (PG_DEBUG = 'Y') THEN
2306         arp_standard.debug('Inserting: '||l_open_invoice_list_rec(trx).trx_number);
2307      END IF;
2308 
2309      ----------------------------------------------------------------------------------------
2310      l_debug_info := 'Calculate discount';
2311      -----------------------------------------------------------------------------------------
2312      IF (PG_DEBUG = 'Y') THEN
2313         arp_standard.debug(l_debug_info);
2314      END IF;
2315 
2316 
2317      arp_discounts_api.get_discount(p_ps_id	        => l_open_invoice_list_rec(trx).payment_schedule_id,
2318 		                    p_apply_date	=> trunc(sysdate),
2319                             	    p_in_applied_amount => l_open_invoice_list_rec(trx).amount_due_remaining - l_open_invoice_list_rec(trx).dispute_amt,
2320 		                    p_grace_days_flag   => l_grace_days_flag,
2321 		                    p_out_discount      => l_open_invoice_list_rec(trx).ORIGINAL_DISCOUNT_AMT,
2322 		                    p_out_rem_amt_rcpt 	=> l_rem_amt_rcpt,
2323 		                    p_out_rem_amt_inv 	=> l_rem_amt_inv,
2324 				    p_called_from	=> 'OIR');
2325 
2326      l_open_invoice_list_rec(trx).discount_amount := l_open_invoice_list_rec(trx).ORIGINAL_DISCOUNT_AMT;
2327 
2328     l_open_invoice_list_rec(trx).PAYING_CUSTOMER_ID := l_open_invoice_list_rec(trx).CUSTOMER_ID;
2329     l_open_invoice_list_rec(trx).PAYING_SITE_USE_ID := l_open_invoice_list_rec(trx).CUSTOMER_SITE_USE_ID;
2330 
2331     --Bug 4479224
2332 	l_open_invoice_list_rec(trx).CUSTOMER_ID := p_customer_id;
2333 	if(p_customer_site_use_id = null) then
2334 		l_open_invoice_list_rec(trx).CUSTOMER_SITE_USE_ID := -1;
2335 	else
2336 		l_open_invoice_list_rec(trx).CUSTOMER_SITE_USE_ID := p_customer_site_use_id;
2337 	end if;
2338 
2339 
2340 
2341     BEGIN
2342 	        l_open_invoice_list_rec(trx).payment_amt  := ARI_UTILITIES.curr_round_amt(l_open_invoice_list_rec(trx).AMOUNT_DUE_REMAINING
2343 		                                           - l_open_invoice_list_rec(trx).discount_amount - l_open_invoice_list_rec(trx).dispute_amt,
2344 							     l_open_invoice_list_rec(trx).INVOICE_CURRENCY_CODE);
2345 
2346     EXCEPTION
2347         WHEN OTHERS THEN
2348             null;
2349     END;
2350     end loop;
2351     FORALL trx
2352     IN l_open_invoice_list_rec.first .. l_open_invoice_list_rec.last
2353     INSERT INTO AR_IREC_PAYMENT_LIST_GT
2354       VALUES l_open_invoice_list_rec(trx);
2355 
2356    ----------------------------------------------------------------------------------------
2357    l_debug_info := 'Compute service charge';
2358    -----------------------------------------------------------------------------------------
2359    IF (PG_DEBUG = 'Y') THEN
2360       arp_standard.debug(l_debug_info);
2361    END IF;
2362    l_total_service_charge := get_service_charge(p_customer_id, p_customer_site_use_id);
2363 
2364    COMMIT;
2365 
2366 EXCEPTION
2367      WHEN OTHERS THEN
2368          IF (PG_DEBUG = 'Y') THEN
2369              arp_standard.debug('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
2370 	     arp_standard.debug('- Customer Id: '||p_customer_id);
2371 	     arp_standard.debug('- Customer Site Use Id: '|| p_customer_site_use_id);
2372 	     arp_standard.debug('- Currency Code: '||p_currency_code);
2373              arp_standard.debug('- Payment Schedule Id: '||p_payment_schedule_id);
2374              arp_standard.debug('ERROR =>'|| SQLERRM);
2375          END IF;
2376 
2377 	 ROLLBACK TO create_invoice_pay_list_sp;
2378 
2379          FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
2380          FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
2381          FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
2382          FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
2383          FND_MSG_PUB.ADD;
2384 END create_invoice_pay_list;
2385 
2386 /*============================================================
2387   | PUBLIC procedure create_open_credit_pay_list
2388   |
2389   | DESCRIPTION
2390   |   Copy all open credit transactions for the active customer, site and currency from the
2391   |   AR_PAYMENT_SCHEDULES to the Payment List GT
2392   |
2393   | PSEUDO CODE/LOGIC
2394   |
2395   | PARAMETERS
2396   |   p_customer_id               IN NUMBER
2397   |   p_customer_site_use_id      IN NUMBER DEFAULT NULL
2398   |   p_currency_code             IN VARCHAR2
2399   |
2400   | KNOWN ISSUES
2401   |
2402   |
2403   |
2404   | NOTES
2405   |
2406   |
2407   |
2408   | MODIFICATION HISTORY
2409   | Date          Author       Description of Changes
2410   | 21-JAN-2004   rsinthre     Created
2411   | 08-Jul-2005	  rsinthre     Bug 4437225 - Disputed amount against invoice not displayed during payment
2412   +============================================================*/
2413 
2414 PROCEDURE create_open_credit_pay_list(p_customer_id           IN NUMBER,
2415                             p_customer_site_use_id  IN NUMBER DEFAULT NULL,
2416                             p_currency_code         IN VARCHAR2
2417                            ) IS
2418   CURSOR credit_transactions_list (p_customer_id NUMBER,
2419                             p_customer_site_use_id NUMBER,
2420                             p_currency_code VARCHAR2) IS
2421   ( SELECT * FROM
2422    (SELECT ps.CUSTOMER_ID,
2423          DECODE(ps.CUSTOMER_SITE_USE_ID,null,-1,ps.CUSTOMER_SITE_USE_ID) as CUSTOMER_SITE_USE_ID,
2424          acct.ACCOUNT_NUMBER,
2425          ps.CUSTOMER_TRX_ID,
2426          ps.TRX_NUMBER,
2427          ps.TRX_DATE,
2428          ps.class,
2429          ps.DUE_DATE,
2430          ps.PAYMENT_SCHEDULE_ID,
2431          ps.STATUS,
2432          trm.name term_desc,
2433          ARPT_SQL_FUNC_UTIL.Get_Number_Of_Due_Dates(ps.term_id) number_of_installments,
2434          ps.terms_sequence_number,
2435          ps.amount_line_items_original line_amount,
2436          ps.tax_original tax_amount,
2437          ps.freight_original freight_amount,
2438          ps.receivables_charges_charged finance_charge,
2439          ps.INVOICE_CURRENCY_CODE,
2440          ps.AMOUNT_DUE_ORIGINAL,
2441          DECODE (ps.class, 'PMT', ar_irec_payments.get_pymt_amnt_due_remaining(ps.cash_receipt_id),ps.AMOUNT_DUE_REMAINING) as AMOUNT_DUE_REMAINING,
2442 	 0 payment_amt,
2443 	 0 service_charge,
2444 	 0 discount_amount,
2445 	 TRUNC(SYSDATE) receipt_date,
2446 	 '' receipt_number,
2447          ct.PURCHASE_ORDER AS PO_NUMBER,
2448          NULL AS SO_NUMBER,
2449          ct.printing_option,
2450 	 ct.INTERFACE_HEADER_CONTEXT,
2451          ct.INTERFACE_HEADER_ATTRIBUTE1,
2452          ct.INTERFACE_HEADER_ATTRIBUTE2,
2453          ct.INTERFACE_HEADER_ATTRIBUTE3,
2454          ct.INTERFACE_HEADER_ATTRIBUTE4,
2455          ct.INTERFACE_HEADER_ATTRIBUTE5,
2456          ct.INTERFACE_HEADER_ATTRIBUTE6,
2457          ct.INTERFACE_HEADER_ATTRIBUTE7,
2458          ct.INTERFACE_HEADER_ATTRIBUTE8,
2459          ct.INTERFACE_HEADER_ATTRIBUTE9,
2460          ct.INTERFACE_HEADER_ATTRIBUTE10,
2461          ct.INTERFACE_HEADER_ATTRIBUTE11,
2462          ct.INTERFACE_HEADER_ATTRIBUTE12,
2463          ct.INTERFACE_HEADER_ATTRIBUTE13,
2464          ct.INTERFACE_HEADER_ATTRIBUTE14,
2465          ct.INTERFACE_HEADER_ATTRIBUTE15,
2466          ps.ATTRIBUTE_CATEGORY,
2467          ps.ATTRIBUTE1,
2468          ps.ATTRIBUTE2,
2469          ps.ATTRIBUTE3,
2470          ps.ATTRIBUTE4,
2471          ps.ATTRIBUTE5,
2472          ps.ATTRIBUTE6,
2473          ps.ATTRIBUTE7,
2474          ps.ATTRIBUTE8,
2475          ps.ATTRIBUTE9,
2476          ps.ATTRIBUTE10,
2477          ps.ATTRIBUTE11,
2478          ps.ATTRIBUTE12,
2479          ps.ATTRIBUTE13,
2480          ps.ATTRIBUTE14,
2481          ps.ATTRIBUTE15,
2482 	 sysdate LAST_UPDATE_DATE,
2483 	 0 LAST_UPDATED_BY,
2484 	 sysdate CREATION_DATE,
2485 	 0 CREATED_BY,
2486 	 0 LAST_UPDATE_LOGIN,
2487 	 0 APPLICATION_AMOUNT,
2488 	 ps.CASH_RECEIPT_ID,
2489 	 0  ORIGINAL_DISCOUNT_AMT,
2490          ps.org_id,
2491 	 0 PAYING_CUSTOMER_ID,
2492 	 0 PAYING_SITE_USE_ID,
2493 	 0  dispute_amt
2494   FROM AR_PAYMENT_SCHEDULES ps,
2495        RA_CUSTOMER_TRX_ALL ct,
2496        HZ_CUST_ACCOUNTS acct,
2497        RA_TERMS trm
2498   WHERE ps.customer_id = p_customer_id
2499   AND   ( ps.CLASS = 'CM'
2500           OR
2501           ps.CLASS = 'PMT'
2502         )
2503   AND   ps.customer_trx_id = ct.customer_trx_id(+)
2504   AND   nvl(ps.customer_site_use_id,-1) = nvl(p_customer_site_use_id, nvl(ps.customer_site_use_id,-1))
2505   AND   acct.cust_account_id = ps.customer_id
2506   AND   ps.status = 'OP'
2507   AND   ps.invoice_currency_code = p_currency_code
2508   AND   ps.term_id = trm.term_id(+))
2509   WHERE AMOUNT_DUE_REMAINING < 0);
2510 
2511    l_procedure_name           VARCHAR2(50);
2512    l_debug_info	 	          VARCHAR2(200);
2513    TYPE t_credit_transactions_list_rec
2514          IS TABLE OF credit_transactions_list%ROWTYPE index by binary_integer ;
2515 
2516    l_credit_transactions_list_rec  t_credit_transactions_list_rec ;
2517 
2518 BEGIN
2519     l_procedure_name           := '.create_open_credit_pay_list';
2520 
2521 
2522     ---------------------------------------------------------------------------
2523     l_debug_info := 'Fetch all open credit transactions into Payment List GT';
2524     ---------------------------------------------------------------------------
2525     IF (PG_DEBUG = 'Y') THEN
2526         arp_standard.debug(l_debug_info);
2527     END IF;
2528 
2529     Open  credit_transactions_list(p_customer_id,
2530                                  p_customer_site_use_id,
2531                                  p_currency_code );
2532     FETCH  credit_transactions_list BULK COLLECT INTO l_credit_transactions_list_rec;
2533       close credit_transactions_list;
2534 
2535     	 FOR trx IN l_credit_transactions_list_rec.first .. l_credit_transactions_list_rec.last loop
2536     		l_credit_transactions_list_rec(trx).payment_amt  := l_credit_transactions_list_rec(trx).AMOUNT_DUE_REMAINING;
2537 	   end loop;
2538 
2539 	 FORALL trx
2540 	   IN l_credit_transactions_list_rec.first .. l_credit_transactions_list_rec.last
2541 
2542 	   INSERT INTO AR_IREC_PAYMENT_LIST_GT
2543 	   VALUES l_credit_transactions_list_rec(trx);
2544 
2545     COMMIT;
2546 
2547 EXCEPTION
2548 WHEN OTHERS THEN
2549       IF (PG_DEBUG = 'Y') THEN
2550         arp_standard.debug('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
2551         arp_standard.debug('- Customer Id: '||p_customer_id);
2552         arp_standard.debug('- Customer Site Use Id: '||p_customer_site_use_id);
2553         arp_standard.debug('- Currency Code: '||p_currency_code);
2554         arp_standard.debug('ERROR =>'|| SQLERRM);
2555       END IF;
2556 
2557       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
2558       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
2559       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
2560       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
2561       FND_MSG_PUB.ADD;
2562 
2563 END create_open_credit_pay_list;
2564 
2565 /*============================================================
2566  | PUBLIC procedure cal_discount_and_service_chrg
2567  |
2568  | DESCRIPTION
2569  |   Calculate discount and service charge on the selected
2570  |   invoices and update the amounts
2571  |
2572  | PSEUDO CODE/LOGIC
2573  |
2574  | PARAMETERS
2575  |
2576  | KNOWN ISSUES
2577  |
2578  |
2579  |
2580  | NOTES
2581  |   This procedure acts on the rows inserted in the global
2582  |   temporary table by the create_invoice_pay_list procedure.
2583  |   It is session specific.
2584  |
2585  |
2586  | MODIFICATION HISTORY
2587  | Date          Author       Description of Changes
2588  | 13-Jan-2003   krmenon      Created
2589  | 26-Apr-2004   vnb          Added Customer and Customer Site as input params.
2590  | 10-Jun-2004   vnb          Bug # 3458134 - Check if the grace days for discount option is
2591  |							  enabled while calculating discount
2592  | 19-Jul-2004   vnb          Bug # 2830823 - Added exception block to handle exceptions
2593  | 31-Dec-2004   vnb          Bug 4071551 - Removed redundant code
2594  | 07-Jul-2005		 rsinthre  Bug 4437220 - Payment amount not changed when discount recalculated
2595  +============================================================*/
2596 PROCEDURE cal_discount_and_service_chrg (p_customer_id	IN NUMBER,
2597                                          p_site_use_id  IN NUMBER DEFAULT NULL,
2598                                          p_receipt_date IN DATE DEFAULT trunc(SYSDATE)) IS
2599   --l_invoice_list        ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE;
2600 
2601   l_total_service_charge  NUMBER;
2602   l_count                 NUMBER;
2603   l_payment_amount        NUMBER;
2604   l_prev_disc_amt         NUMBER;
2605   l_discount_amount       NUMBER;
2606   l_amt_due_remaining     NUMBER;
2607   l_rem_amt_rcpt          NUMBER;
2608   l_rem_amt_inv           NUMBER;
2609   l_grace_days_flag          VARCHAR2(2);
2610 
2611   l_procedure_name           VARCHAR2(50);
2612   l_debug_info               VARCHAR2(200);
2613 
2614   --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
2615   --Bug 4062938 - Select only debit transactions
2616   CURSOR invoice_list IS
2617     SELECT  payment_schedule_id,
2618             receipt_date,
2619             payment_amt as payment_amount,
2620             amount_due_remaining,
2621             discount_amount,
2622             customer_id,
2623             account_number,
2624             customer_trx_id,
2625             currency_code,
2626             service_charge
2627     FROM AR_IREC_PAYMENT_LIST_GT
2628     WHERE customer_id = p_customer_id
2629     AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
2630     AND trx_class in ('INV','DEP', 'DM', 'CB')
2631     FOR UPDATE;
2632 
2633 BEGIN
2634    --Assign default values
2635    l_total_service_charge     := 0;
2636    l_discount_amount          := 0;
2637    l_payment_amount           := 0;
2638    l_prev_disc_amt            := 0;
2639    l_amt_due_remaining        := 0;
2640    l_rem_amt_rcpt             := 0;
2641    l_rem_amt_inv              := 0;
2642    l_procedure_name           := '.cal_discount_and_service_chrg';
2643 
2644    SAVEPOINT cal_disc_and_service_charge_sp;
2645 
2646    -- Check if grace days have to be considered for discount.
2647    --l_grace_days_flag := is_grace_days_enabled_wrapper();
2648    l_grace_days_flag := ARI_UTILITIES.is_discount_grace_days_enabled(p_customer_id,p_site_use_id);
2649 
2650    -- Create the invoice list table
2651    FOR invoice_rec in invoice_list
2652    LOOP
2653       ---------------------------------------------------------------------------
2654       l_debug_info := 'Calculate discount';
2655       ---------------------------------------------------------------------------
2656       IF (PG_DEBUG = 'Y') THEN
2657          arp_standard.debug(l_debug_info);
2658       END IF;
2659       l_prev_disc_amt       := invoice_rec.discount_amount;
2660       l_payment_amount          := invoice_rec.payment_amount;
2661       l_amt_due_remaining   := invoice_rec.amount_due_remaining;
2662       arp_discounts_api.get_discount(  p_ps_id	            => invoice_rec.payment_schedule_id,
2663 		                       p_apply_date	    => trunc(p_receipt_date),
2664                             	       p_in_applied_amount  => invoice_rec.payment_amount,
2665 		                       p_grace_days_flag    => l_grace_days_flag,
2666 		                       p_out_discount       => l_discount_amount,
2667 		                       p_out_rem_amt_rcpt   => l_rem_amt_rcpt,
2668 		                       p_out_rem_amt_inv    => l_rem_amt_inv);
2669 
2670       IF (PG_DEBUG = 'Y') THEN
2671          arp_standard.debug('Trx: '||invoice_rec.payment_schedule_id||
2672 	                         ' Discount: '||l_discount_amount||
2673 	                         ' Rcpt: '||l_rem_amt_rcpt||
2674 		                 ' Inv: '||l_rem_amt_inv);
2675       END IF;
2676 
2677      	-- Bug 4352272 - Support both positive and negative invoices
2678 	if((abs(l_payment_amount + l_discount_amount) > abs(l_amt_due_remaining)) OR (abs(l_payment_amount + l_prev_disc_amt) = abs(l_amt_due_remaining))) then
2679 		l_payment_amount := l_amt_due_remaining - l_discount_amount;
2680 	end if;
2681 
2682 
2683 
2684       -----------------------------------------------------------------------------------------
2685       l_debug_info := 'Update transaction list with discount and receipt date';
2686       -----------------------------------------------------------------------------------------
2687       IF (PG_DEBUG = 'Y') THEN
2688          arp_standard.debug(l_debug_info);
2689       END IF;
2690       UPDATE AR_IREC_PAYMENT_LIST_GT
2691       SET discount_amount = l_discount_amount,
2692 	      receipt_date    = trunc(p_receipt_date),
2693           payment_amt = l_payment_amount
2694       WHERE CURRENT OF invoice_list;
2695 
2696    END LOOP;
2697 
2698    -----------------------------------------------------------------------------------------
2699    l_debug_info := 'Compute service charge';
2700    -----------------------------------------------------------------------------------------
2701    IF (PG_DEBUG = 'Y') THEN
2702       arp_standard.debug(l_debug_info);
2703    END IF;
2704    -- Bug # 3467287 - The service charge calculator API is striped by
2705    --                 Customer and Customer Site.
2706    -- Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.is_service_charge_enabled
2707    l_total_service_charge := get_service_charge(p_customer_id, p_site_use_id);
2708 
2709    --COMMIT;
2710 
2711 EXCEPTION
2712     WHEN OTHERS THEN
2713     	BEGIN
2714             write_debug_and_log('Unexpected Exception while calculating discount and service charge');
2715             write_debug_and_log('- Customer Id: '||p_customer_id);
2716             write_debug_and_log('- Customer Site Id: '||p_site_use_id);
2717             write_debug_and_log('- Total Service charge: '||l_total_service_charge);
2718             write_debug_and_log(SQLERRM);
2719         END;
2720 
2721 	ROLLBACK TO cal_disc_and_service_charge_sp;
2722 
2723 	FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
2724         FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
2725         FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
2726         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
2727         FND_MSG_PUB.ADD;
2728 
2729 END cal_discount_and_service_chrg;
2730 
2731 /*============================================================
2732  | procedure create_payment_instrument
2733  |
2734  | DESCRIPTION
2735  |   Creates a payment instrument with the given details
2736  |
2737  | PSEUDO CODE/LOGIC
2738  |
2739  | PARAMETERS
2740  |
2741  | KNOWN ISSUES
2742  |
2743  |
2744  |
2745  | NOTES
2746  |
2747  |
2748  |
2749  | MODIFICATION HISTORY
2750  | Date          Author       Description of Changes
2751  | 15-Jun-2005   rsinthre     Created
2752  | 18-Oct-2005	 rsinthre     Bug 4673563 - Error making credit card payment
2753  +============================================================*/
2754  PROCEDURE create_payment_instrument (  p_customer_id         IN NUMBER,
2755 					p_customer_site_id    IN NUMBER,
2756 					p_account_number      IN VARCHAR2,
2757 					p_payer_party_id      IN NUMBER,
2758 					p_expiration_date     IN DATE,
2759 					p_account_holder_name IN VARCHAR2,
2760 					p_account_type        IN VARCHAR2,
2761 					p_payment_instrument  IN VARCHAR2,
2762 					p_address_country     IN VARCHAR2 default null,
2763 					p_bank_branch_id      IN NUMBER ,
2764 					p_receipt_curr_code   IN VARCHAR2,
2765 					p_bank_id	      IN NUMBER,
2766 					p_card_brand	      IN VARCHAR2,
2767 					p_cc_bill_to_site_id  IN NUMBER,
2768 					p_single_use_flag     IN VARCHAR2,
2769 					p_iban		      IN VARCHAR2,
2770 					p_status              OUT NOCOPY VARCHAR2,
2771 					x_msg_count           OUT NOCOPY NUMBER,
2772 					x_msg_data            OUT NOCOPY VARCHAR2,
2773 				        p_assignment_id       OUT NOCOPY NUMBER,
2774 				        p_bank_account_id     OUT NOCOPY NUMBER) IS
2775 
2776 
2777   l_create_credit_card		IBY_FNDCPT_SETUP_PUB.CreditCard_rec_type;
2778   l_ext_bank_act_rec		IBY_EXT_BANKACCT_PUB.ExtBankAcct_rec_type;
2779   l_result_rec			IBY_FNDCPT_COMMON_PUB.Result_rec_type;
2780   l_location_rec		HZ_LOCATION_V2PUB.LOCATION_REC_TYPE;
2781   l_party_site_rec		HZ_PARTY_SITE_V2PUB.party_site_rec_type;
2782   l_payerContext_Rec_type	IBY_FNDCPT_COMMON_PUB.PayerContext_Rec_type;
2783   l_pmtInstrAssignment_Rec_type	IBY_FNDCPT_SETUP_PUB.PmtInstrAssignment_rec_type;
2784   l_pmtInstr_rec_type		IBY_FNDCPT_SETUP_PUB.PmtInstrument_rec_type;
2785 
2786   l_payer_attibute_id		NUMBER(15,0);
2787 
2788   l_instrument_type		VARCHAR2(20);
2789   l_assignment_id		NUMBER(15,0);
2790   l_bank_account_id		NUMBER;
2791   x_return_status               VARCHAR2(100);
2792   l_procedure_name		VARCHAR2(30);
2793   l_debug_info	 	        VARCHAR2(200);
2794   l_commit                      VARCHAR2(2);
2795 
2796 BEGIN
2797 
2798   l_procedure_name  := '.create_payment_instrument';
2799   l_commit :=  FND_API.G_FALSE;
2800 
2801   IF (p_payment_instrument = 'BANK_ACCOUNT') THEN
2802   --------------------------------------------------------------------------------------------------------
2803   l_debug_info := 'Call IBY create external bank acct - create_ext_bank_acct - to Create a new bank account';
2804    ---------------------------------------------------------------------------------------------------------
2805 
2806 	    l_ext_bank_act_rec.acct_owner_party_id		:=  p_payer_party_id;
2807 	    l_ext_bank_act_rec.country_code			:= p_address_country;
2808 	    l_ext_bank_act_rec.branch_id			:= p_bank_branch_id;
2809 	    l_ext_bank_act_rec.bank_id				:= p_bank_id;
2810 	    l_ext_bank_act_rec.bank_account_name		:= p_account_holder_name;
2811 	    l_ext_bank_act_rec.bank_account_num			:= p_account_number;
2812 	    l_ext_bank_act_rec.currency				:= p_receipt_curr_code;
2813 	    l_ext_bank_act_rec.multi_currency_allowed_flag	:= 'Y';
2814 	    l_ext_bank_act_rec.acct_type			:= p_account_type;
2815 	    l_ext_bank_act_rec.iban				:= p_iban;
2816 
2817 	  IBY_EXT_BANKACCT_PUB.create_ext_bank_acct(
2818 	    p_api_version                => 1.0,
2819 	    p_init_msg_list            	 => FND_API.G_FALSE,
2820 	    p_ext_bank_acct_rec          => l_ext_bank_act_rec,
2821 	    x_acct_id			 => l_bank_account_id,
2822 	    x_return_status            	 => x_return_status,
2823 	    x_msg_count                	 => x_msg_count,
2824 	    x_msg_data                 	 => x_msg_data,
2825 	    x_response                   => l_result_rec);
2826 
2827 	    write_debug_and_log('l_bank_account_id :'||l_bank_account_id);
2828 	    IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
2829 		  x_msg_data := l_result_rec.result_code;
2830 	          p_status := FND_API.G_RET_STS_ERROR;
2831 	          write_error_messages(x_msg_data, x_msg_count);
2832 	          RETURN;
2833 	   END IF;
2834 
2835    ELSE
2836 -----------------------------------------------------------------------------------------
2837   l_debug_info := 'Call IBY create card - Create_Card - to Create a new CC';
2838 -----------------------------------------------------------------------------------------
2839 
2840 	  l_create_credit_card.Card_Id                   := NULL;
2841 	  l_create_credit_card.Owner_Id                  := p_payer_party_id;
2842 	  l_create_credit_card.Card_Holder_Name          := p_account_holder_name;
2843 	  if p_cc_bill_to_site_id > 0 then
2844 		  l_create_credit_card.Billing_Address_Id        := p_cc_bill_to_site_id;
2845 		  l_create_credit_card.Billing_Postal_Code       := NULL;
2846 		  l_create_credit_card.Billing_Address_Territory := NULL;
2847 	  else
2848 		  l_create_credit_card.Billing_Address_Id        := NULL;
2849 		  l_create_credit_card.Billing_Postal_Code       := 94065;
2850 		  l_create_credit_card.Billing_Address_Territory := 'US';
2851 	  end if;
2852 	  l_create_credit_card.Card_Number               := p_account_number;
2853 	  l_create_credit_card.Expiration_Date           := p_expiration_date;
2854 	  l_create_credit_card.Instrument_Type           := 'CREDITCARD';
2855 	  l_create_credit_card.PurchaseCard_SubType      := NULL;
2856 	  l_create_credit_card.Card_Issuer               := p_card_brand;
2857 	  l_create_credit_card.Single_Use_Flag           := p_single_use_flag;
2858 	  l_create_credit_card.Info_Only_Flag            := 'N';
2859 
2860 	IBY_FNDCPT_SETUP_PUB.create_card(
2861 	 p_api_version      => 1.0,
2862 	 p_init_msg_list    => FND_API.G_FALSE,
2863 	 p_commit           => l_commit,
2864 	 x_return_status    => x_return_status,
2865 	 x_msg_count        => x_msg_count,
2866 	 x_msg_data         => x_msg_data,
2867 	 p_card_instrument  => l_create_credit_card,
2868 	 x_card_id          => l_bank_account_id,
2869 	 x_response         => l_result_rec);
2870 
2871         write_debug_and_log('l_card_id :'||l_bank_account_id);
2872 	IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
2873 	          p_status := FND_API.G_RET_STS_ERROR;
2874                   x_msg_data := l_result_rec.result_code;
2875 	          write_error_messages(x_msg_data, x_msg_count);
2876 	          RETURN;
2877 	END IF;
2878   END IF;
2879 
2880 	--Now assign the instrument to the payer.
2881 	-----------------------------------------------------------------------------------------
2882 	  l_debug_info := 'Call IBY Instrumnet Assignment - To assign instrument';
2883 	-----------------------------------------------------------------------------------------
2884 	if(p_payment_instrument = 'BANK_ACCOUNT') then
2885 		l_instrument_type := 'BANKACCOUNT';
2886 	else
2887 		l_instrument_type := 'CREDITCARD';
2888 	end if;
2889 
2890 	l_payerContext_Rec_type.Payment_Function	:= 'CUSTOMER_PAYMENT';
2891 	l_payerContext_Rec_type.Party_Id		:= p_payer_party_id;
2892 	l_payerContext_Rec_type.Cust_Account_Id		:= p_customer_id;
2893 	if(p_customer_site_id is not null) then
2894 		l_payerContext_Rec_type.Org_Type		:= 'OPERATING_UNIT';
2895 		l_payerContext_Rec_type.Org_Id			:= mo_global.get_current_org_id;
2896 		l_payerContext_Rec_type.Account_Site_id		:= p_customer_site_id;
2897 	end if;
2898 
2899 
2900 	l_pmtInstr_rec_type.Instrument_type := l_instrument_type;
2901 	l_pmtInstr_rec_type.Instrument_Id   := l_bank_account_id;
2902 
2903 	l_pmtInstrAssignment_Rec_type.Assignment_Id	:= NULL;
2904 	l_pmtInstrAssignment_Rec_type.Instrument	:= l_pmtInstr_rec_type;
2905 	l_pmtInstrAssignment_Rec_type.Priority		:= 1;
2906 	l_pmtInstrAssignment_Rec_type.Start_Date	:= sysdate;
2907 	l_pmtInstrAssignment_Rec_type.End_Date		:= NULL;
2908 
2909 
2910 	IBY_FNDCPT_SETUP_PUB.Set_Payer_Instr_Assignment(
2911 		    p_api_version      => 1.0,
2912 		    p_init_msg_list    => FND_API.G_FALSE,
2913 		    p_commit           => FND_API.G_TRUE,
2914 		    x_return_status    => x_return_status,
2915 		    x_msg_count        => x_msg_count,
2916 		    x_msg_data         => x_msg_data,
2917 		    p_payer            => l_payerContext_Rec_type,
2918 		    p_assignment_attribs => l_pmtInstrAssignment_Rec_type,
2919 		    x_assign_id        => l_assignment_id,
2920 		    x_response         => l_result_rec
2921 	);
2922 
2923 	IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
2924 		  p_status := FND_API.G_RET_STS_ERROR;
2925 		  x_msg_data := l_result_rec.result_code;
2926 		  write_error_messages(x_msg_data, x_msg_count);
2927 		  RETURN;
2928 	END IF;
2929 	p_assignment_id := l_assignment_id;
2930 	p_bank_account_id := l_bank_account_id;
2931 	p_status := x_return_status;
2932 
2933 	write_debug_and_log('instrument_assignment_id :'||p_assignment_id );
2934 
2935 	   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
2936 		fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Payment Instrument - Return status - '||x_return_status);
2937 		fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Payment Instrument - Message Count - '||x_msg_count);
2938 		fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Payment Instrument - Message Data - '||x_msg_data);
2939 		fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Payment Instrument - Credit Card Number - '||p_account_number);
2940 	  end if;
2941 
2942 	  IF (PG_DEBUG = 'Y') THEN
2943 	    arp_standard.debug(l_debug_info);
2944 	  END IF;
2945 
2946 
2947 EXCEPTION
2948     WHEN OTHERS THEN
2949       p_status := FND_API.G_RET_STS_ERROR;
2950       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
2951       write_debug_and_log('- Card Number: '||p_account_number);
2952       write_debug_and_log('- CC Billing Addrress Site Id: '||p_cc_bill_to_site_id);
2953       write_debug_and_log('- Singe Use Flag: '||p_single_use_flag);
2954       write_debug_and_log('- Return Status: '||p_status);
2955       write_debug_and_log('ERROR =>'|| SQLERRM);
2956 
2957       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
2958       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
2959       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
2960       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
2961       FND_MSG_PUB.ADD;
2962 END create_payment_instrument;
2963 
2964 /*============================================================
2965  | procedure create_cc_bill_to_site
2966  |
2967  | DESCRIPTION
2968  |   Creates/Updates Credit card bill to location with the given details
2969  |
2970  | PSEUDO CODE/LOGIC
2971  |
2972  | PARAMETERS
2973  |
2974  | KNOWN ISSUES
2975  |
2976  |
2977  |
2978  | NOTES
2979  |
2980  |
2981  |
2982  | MODIFICATION HISTORY
2983  | Date          Author       Description of Changes
2984  | 17-Aug-2005   rsinthre     Created
2985  +============================================================*/
2986 PROCEDURE create_cc_bill_to_site(
2987 		p_init_msg_list		IN   VARCHAR2  := FND_API.G_FALSE,
2988 		p_commit		IN   VARCHAR2  := FND_API.G_TRUE,
2989 		p_cc_location_rec	IN   HZ_LOCATION_V2PUB.LOCATION_REC_TYPE,
2990 		p_payer_party_id	IN   NUMBER,
2991 		x_cc_bill_to_site_id	IN OUT  NOCOPY NUMBER,
2992 		x_return_status		OUT NOCOPY VARCHAR2,
2993 		x_msg_count		OUT NOCOPY NUMBER,
2994 		x_msg_data		OUT NOCOPY VARCHAR2) IS
2995 
2996 l_location_id			NUMBER(15,0);
2997 l_location_rec			HZ_LOCATION_V2PUB.LOCATION_REC_TYPE;
2998 l_party_site_rec		HZ_PARTY_SITE_V2PUB.party_site_rec_type;
2999 l_party_site_number		VARCHAR2(30);
3000 l_object_version_number		NUMBER(15,0);
3001 CURSOR location_id_cur IS
3002 	select hps.location_id, hl.object_version_number from hz_party_sites hps, hz_locations hl where party_site_id = x_cc_bill_to_site_id
3003 	and hps.location_id = hl.location_id;
3004   location_id_rec	location_id_cur%ROWTYPE;
3005 
3006 l_procedure_name		VARCHAR2(30);
3007 l_debug_info	 	        VARCHAR2(200);
3008 
3009 BEGIN
3010 	l_procedure_name  := '.create_cc_bill_to_site';
3011 	-----------------------------------------------------------------------------------------
3012 	 l_debug_info := 'Call TCA create location - create_location - to create location for new CC';
3013 	-----------------------------------------------------------------------------------------
3014 
3015 		hz_location_v2pub.create_location(
3016 		    p_init_msg_list              => p_init_msg_list,
3017 		    p_location_rec               => p_cc_location_rec,
3018 		    x_location_id                => l_location_id,
3019 		    x_return_status              => x_return_status,
3020 		    x_msg_count                  => x_msg_count,
3021 		    x_msg_data                   => x_msg_data);
3022 
3023 		    IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
3024 		      x_return_status := FND_API.G_RET_STS_ERROR;
3025 		      write_error_messages(x_msg_data, x_msg_count);
3026 		      RETURN;
3027 		    END IF;
3028 
3029                 write_debug_and_log('cc_billing_location_id :'||l_location_id);
3030 
3031 		l_party_site_rec.party_id := p_payer_party_id;
3032 		l_party_site_rec.location_id := l_location_id;
3033 		l_party_site_rec.identifying_address_flag := 'N';
3034 		l_party_site_rec.created_by_module := 'ARI';
3035 
3036 		hz_party_site_v2pub.create_party_site (
3037 		p_init_msg_list         => p_init_msg_list,
3038 		p_party_site_rec        => l_party_site_rec,
3039 		x_party_site_id         => x_cc_bill_to_site_id,
3040 		x_party_site_number     => l_party_site_number,
3041 		x_return_status         => x_return_status,
3042 		x_msg_count             => x_msg_count,
3043 		x_msg_data              => x_msg_data
3044 		);
3045 
3046 		write_debug_and_log('cc_billing_site_id :'||x_cc_bill_to_site_id);
3047 
3048 		IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
3049 	          x_return_status := FND_API.G_RET_STS_ERROR;
3050 	          write_error_messages(x_msg_data, x_msg_count);
3051 	          RETURN;
3052 		END IF;
3053 
3054 EXCEPTION
3055     WHEN OTHERS THEN
3056       x_return_status := FND_API.G_RET_STS_ERROR;
3057 
3058       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
3059       write_debug_and_log('- Return Status: '||x_return_status);
3060       write_debug_and_log('ERROR =>'|| SQLERRM);
3061 
3062       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
3063       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
3064       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3065       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
3066       FND_MSG_PUB.ADD;
3067 
3068 END create_cc_bill_to_site;
3069 
3070 /*============================================================
3071  | PUBLIC procedure create_receipt
3072  |
3073  | DESCRIPTION
3074  |   Creates a cash receipt fpr the given customer
3075  |
3076  | PSEUDO CODE/LOGIC
3077  |
3078  | PARAMETERS
3079  |
3080  | KNOWN ISSUES
3081  |
3082  |
3083  |
3084  | NOTES
3085  |
3086  |
3087  |
3088  | MODIFICATION HISTORY
3089  | Date          Author       Description of Changes
3090  | 13-Jan-2003   krmenon      Created
3091  | 17-Nov-2004   vnb          Bug 4000279 - Modified to return error message, if any
3092  +============================================================*/
3093  PROCEDURE create_receipt (p_payment_amount		IN NUMBER,
3094                            p_customer_id		IN NUMBER,
3095                            p_site_use_id		IN NUMBER,
3096                            p_bank_account_id		IN NUMBER,
3097                            p_receipt_date		IN DATE DEFAULT trunc(SYSDATE),
3098                            p_receipt_method_id		IN NUMBER,
3099                            p_receipt_currency_code	IN VARCHAR2,
3100                            p_receipt_exchange_rate	IN NUMBER,
3101                            p_receipt_exchange_rate_type IN VARCHAR2,
3102                            p_receipt_exchange_rate_date IN DATE,
3103                            p_trxn_extn_id		IN NUMBER,
3104                            p_cash_receipt_id		OUT NOCOPY NUMBER,
3105                            p_status			OUT NOCOPY VARCHAR2,
3106                            x_msg_count			OUT NOCOPY NUMBER,
3107                            x_msg_data			OUT NOCOPY VARCHAR2) IS
3108 
3109   l_receipt_method_id       AR_CASH_RECEIPTS_ALL.RECEIPT_METHOD_ID%TYPE;
3110   l_receipt_creation_status VARCHAR2(80);
3111   l_cash_receipt_id         AR_CASH_RECEIPTS_ALL.CASH_RECEIPT_ID%TYPE;
3112   x_return_status           VARCHAR2(100);
3113 
3114   l_procedure_name           VARCHAR2(30);
3115   l_debug_info	 	     VARCHAR2(200);
3116   l_instr_assign_id	     NUMBER;
3117 
3118 BEGIN
3119 
3120   l_procedure_name  := '.create_receipt';
3121 
3122   fnd_log_repository.init;
3123 
3124   -----------------------------------------------------------------------------------------
3125   l_debug_info := 'Call public AR receipts API - create_cash - to create receipt for payment';
3126   -----------------------------------------------------------------------------------------
3127   write_debug_and_log('p_payment_amount:'||p_payment_amount);
3128   write_debug_and_log('p_receipt_method_id:'||p_receipt_method_id);
3129   write_debug_and_log('p_trxn_extn_id:'||p_trxn_extn_id);
3130   write_debug_and_log('p_customer_id:'||p_customer_id);
3131   write_debug_and_log('p_site_use_id:'||p_site_use_id);
3132   write_debug_and_log('p_receipt_currency_code:'||p_receipt_currency_code);
3133   -------------------------------------------------------------------------------------------
3134 
3135   AR_RECEIPT_API_PUB.create_cash(
3136             p_api_version           => 1.0,
3137             p_init_msg_list         => FND_API.G_TRUE,
3138     	    p_commit                => FND_API.G_FALSE,
3139             p_validation_level      => FND_API.G_VALID_LEVEL_FULL,
3140             x_return_status         => x_return_status,
3141             x_msg_count             => x_msg_count,
3142             x_msg_data              => x_msg_data,
3143             p_amount                => p_payment_amount,
3144             p_receipt_method_id     => p_receipt_method_id,
3145             p_customer_id           => p_customer_id,
3146             p_customer_site_use_id  => p_site_use_id,
3147             p_payment_trxn_extension_id     => p_trxn_extn_id,
3148             p_currency_code         => p_receipt_currency_code,
3149             p_exchange_rate         => p_receipt_exchange_rate,
3150             p_exchange_rate_type    => p_receipt_exchange_rate_type,
3151             p_exchange_rate_date    => p_receipt_exchange_rate_date,
3152             p_receipt_date          => trunc(p_receipt_date),
3153             p_gl_date               => trunc(p_receipt_date),
3154             p_cr_id                 => l_cash_receipt_id,
3155             p_called_from           => 'IREC');
3156 
3157   p_cash_receipt_id := l_cash_receipt_id;
3158   p_status := x_return_status;
3159   write_debug_and_log('p_receipt_currency_code:'||l_cash_receipt_id);
3160 
3161   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3162 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Cash - Rerturn status - '||x_return_status);
3163 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Cash - Message Count - '||x_msg_count);
3164 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Cash - Message Data - '||x_msg_data);
3165 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Create Cash - CR Id - '||l_cash_receipt_id);
3166   end if;
3167 
3168   arp_standard.debug('X_RETURN_STATUS=>'||X_RETURN_STATUS);
3169   arp_standard.debug('X_MSG_COUNT=>'||to_char(X_MSG_COUNT));
3170 
3171 EXCEPTION
3172     WHEN OTHERS THEN
3173       p_status := FND_API.G_RET_STS_ERROR;
3174 
3175       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
3176       write_debug_and_log('- Customer Id: '||p_customer_id);
3177       write_debug_and_log('- Customer Site Id: '||p_site_use_id);
3178       write_debug_and_log('- Cash Receipt Id: '||p_cash_receipt_id);
3179       write_debug_and_log('- Bank Account Id: '||p_bank_account_id);
3180       write_debug_and_log('- Return Status: '||p_status);
3181       write_debug_and_log('ERROR =>'|| SQLERRM);
3182 
3183       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
3184       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
3185       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3186       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
3187       FND_MSG_PUB.ADD;
3188 
3189 END create_receipt;
3190 
3191 /*=============================================================
3192  | HISTORY
3193  |  17-Nov-2004   vnb          Bug 4000279 - Modified to return error message, if any
3194  |
3195  | PARAMETERS
3196  |
3197  |   p_customer_id          IN    Customer Id
3198  |   p_site_use_id          IN    Customer Site Id
3199  |   p_cash_receipt_id      IN    Cash Receipt Id
3200  |   p_return_status       OUT    Success/Error status
3201  |   p_apply_err_count     OUT    Number of unsuccessful applications
3202  |
3203  +=============================================================*/
3204 PROCEDURE apply_cash ( p_customer_id		    IN NUMBER,
3205                        p_site_use_id            IN NUMBER DEFAULT NULL,
3206                        p_cash_receipt_id        IN NUMBER,
3207                        p_return_status         OUT NOCOPY VARCHAR2,
3208                        p_apply_err_count       OUT NOCOPY NUMBER,
3209                        x_msg_count           OUT NOCOPY NUMBER,
3210                        x_msg_data            OUT NOCOPY VARCHAR2
3211                      ) IS
3212 
3213 --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
3214 CURSOR credit_trx_list IS
3215   SELECT *
3216   FROM ar_irec_payment_list_gt
3217   WHERE customer_id = p_customer_id
3218   AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
3219   AND ( trx_class = 'CM'
3220           OR
3221         trx_class = 'PMT'
3222 	  );
3223 
3224 CURSOR debit_trx_list IS
3225   SELECT *
3226   FROM ar_irec_payment_list_gt
3227   WHERE customer_id = p_customer_id
3228   AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
3229   AND ( trx_class = 'INV' OR
3230          trx_class = 'DM' OR
3231          trx_class = 'GUAR' OR
3232          trx_class = 'CB' OR
3233          trx_class = 'DEP'
3234 	   )
3235   ORDER BY amount_due_remaining ASC;
3236 
3237   x_return_status           VARCHAR2(100);
3238 
3239   l_msg_count               NUMBER;
3240   l_msg_data                VARCHAR2(255);
3241   l_apply_err_count         NUMBER;
3242 
3243   l_application_ref_num        ar_receivable_applications.application_ref_num%TYPE;
3244   l_receivable_application_id  ar_receivable_applications.receivable_application_id%TYPE;
3245   l_applied_rec_app_id         ar_receivable_applications.receivable_application_id%TYPE;
3246   l_acctd_amount_applied_from  ar_receivable_applications.acctd_amount_applied_from%TYPE;
3247   l_acctd_amount_applied_to    ar_receivable_applications.acctd_amount_applied_to%TYPE;
3248 
3249   l_procedure_name VARCHAR2(30);
3250   l_debug_info	   VARCHAR2(200);
3251 
3252  credit_trx_list_count NUMBER;
3253  debit_trx_list_count NUMBER;
3254  total_trx_count NUMBER;
3255 
3256 BEGIN
3257 
3258   --Assign default values
3259   l_msg_count       := 0;
3260   l_apply_err_count := 0;
3261   l_procedure_name  := '.apply_cash';
3262 
3263     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3264     fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'In apply_cash: p_customer_id='||p_customer_id ||','
3265 	              || 'p_site_use_id=' || p_site_use_id || ','
3266 	              || 'p_cash_receipt_id=' || p_cash_receipt_id);
3267     end if;
3268 
3269     --Pring in the debug log : Total No of rows in ar_irec_payment_list_gt
3270 
3271   SELECT COUNT(*)
3272   INTO 	 total_trx_count
3273   FROM 	 ar_irec_payment_list_gt;
3274 
3275   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3276      fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Total no of rows in ar_irec_payment_list_gt='||total_trx_count);
3277   end if;
3278 
3279 --Pring in the debug log : No of rows that will be picked by the cursor credit_trx_list
3280 
3281   SELECT  COUNT(*)
3282   INTO    credit_trx_list_count
3283   FROM    ar_irec_payment_list_gt
3284   WHERE   customer_id = p_customer_id
3285   AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
3286   AND ( trx_class = 'CM'  OR trx_class = 'PMT' );
3287 
3288   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3289      fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'credit_trx_list_count: '||credit_trx_list_count);
3290   end if;
3291 
3292 --Pring in the debug log : No of rows that will be picked by the cursor debit_trx_list
3293 
3294   SELECT  count(*)
3295   INTO    debit_trx_list_count
3296   FROM    ar_irec_payment_list_gt
3297   WHERE   customer_id = p_customer_id
3298   AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
3299   AND ( trx_class = 'INV' OR
3300          trx_class = 'DM' OR
3301          trx_class = 'GUAR' OR
3302          trx_class = 'CB' OR
3303          trx_class = 'DEP'
3304 	   );
3305 
3306   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3307      fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'debit_trx_list_count: ' || debit_trx_list_count);
3308   end if;
3309 
3310   --
3311   -- Establish a save point
3312   --
3313   SAVEPOINT ARI_Apply_Cash_Receipt_PVT;
3314 
3315   ----------------------------------------------------------------------------------
3316   l_debug_info := 'Step 1: Apply credits against the receipt (if any)';
3317   ----------------------------------------------------------------------------------
3318 
3319     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3320        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
3321     end if;
3322 
3323   FOR trx in credit_trx_list
3324   LOOP
3325 
3326   	if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3327 	    fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, 'trx.trx_class=' || trx.trx_class);
3328         end if;
3329 
3330         IF (trx.trx_class = 'CM') THEN
3331         -- The transaction is a credit memo
3332 
3333         if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3334               fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Calling AR_RECEIPT_API_PUB.apply for CM:'
3335                   ||'trx.customer_trx_id=' || trx.customer_trx_id || ','
3336                   ||'trx.terms_sequence_number=' || trx.terms_sequence_number || ','
3337                   ||'trx.payment_schedule_id=' || trx.payment_schedule_id || ','
3338                   ||'trx.payment_amt=' || trx.payment_amt || ','
3339                   ||'trx.discount_amount=' || trx.discount_amount);
3340         end if;
3341 
3342             AR_RECEIPT_API_PUB.apply(
3343                             p_api_version           => 1.0,
3344                             p_init_msg_list         => FND_API.G_TRUE,
3345                             p_commit                => FND_API.G_FALSE,
3346                             p_validation_level      => FND_API.G_VALID_LEVEL_FULL,
3347                             x_return_status         => x_return_status,
3348                             x_msg_count             => x_msg_count,
3349                             x_msg_data              => x_msg_data,
3350                             p_cash_receipt_id       => p_cash_receipt_id,
3351                             p_customer_trx_id       => trx.customer_trx_id,
3352                             p_installment           => trx.terms_sequence_number,
3353                             p_applied_payment_schedule_id => trx.payment_schedule_id,
3354                             p_amount_applied        => trx.payment_amt,
3355                             p_discount              => trx.discount_amount,
3356 			    p_apply_date            => trunc(trx.receipt_date),
3357                             p_called_from           => 'IREC'
3358                             );
3359 
3360 	   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3361 	        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Execution of AR_RECEIPT_API_PUB.apply is over');
3362 	   end if;
3363 
3364         ELSE
3365         -- The transaction must be a payment
3366 
3367           if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3368               fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Calling AR_RECEIPT_API_PUB.apply_open_receipt for PMT:'
3369               || 'trx.cash_receipt_id='  || trx.cash_receipt_id ||','
3370               || 'trx.payment_amt=' || trx.payment_amt || ','
3371               || 'l_application_ref_num=' || l_application_ref_num || ','
3372               || 'l_receivable_application_id=' || l_receivable_application_id || ','
3373               || 'l_applied_rec_app_id=' || l_applied_rec_app_id || ','
3374               || 'l_acctd_amount_applied_from=' || l_acctd_amount_applied_from || ','
3375               || 'l_acctd_amount_applied_to=' || l_acctd_amount_applied_to);
3376 	    end if;
3377 
3378             AR_RECEIPT_API_PUB.apply_open_receipt
3379                             (p_api_version                 => 1.0,
3380                              p_init_msg_list               => FND_API.G_TRUE,
3381                              p_commit                      => FND_API.G_FALSE,
3382                              x_return_status               => x_return_status,
3383                              x_msg_count                   => x_msg_count,
3384                              x_msg_data                    => x_msg_data,
3385                              p_cash_receipt_id             => p_cash_receipt_id,
3386                              p_open_cash_receipt_id        => trx.cash_receipt_id,
3387                              p_amount_applied              => trx.payment_amt,
3388                              p_called_from                 => 'IREC',
3389                              x_application_ref_num         => l_application_ref_num,
3390                              x_receivable_application_id   => l_receivable_application_id,
3391                              x_applied_rec_app_id          => l_applied_rec_app_id,
3392                              x_acctd_amount_applied_from   => l_acctd_amount_applied_from,
3393                              x_acctd_amount_applied_to     => l_acctd_amount_applied_to
3394                              );
3395 
3396 	   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3397 	        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Execution of AR_RECEIPT_API_PUB.apply_open_receipt is over');
3398 	   end if;
3399 
3400         END IF;
3401 
3402           if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3403 	        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'x_return_status=' || x_return_status);
3404 	   end if;
3405 
3406         -- Check for errors and increment the count for
3407         -- errored applcations
3408         IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
3409             l_apply_err_count := l_apply_err_count + 1;
3410             p_apply_err_count := l_apply_err_count;
3411             p_return_status   := FND_API.G_RET_STS_ERROR;
3412             ROLLBACK TO ARI_Apply_Cash_Receipt_PVT;
3413             RETURN;
3414         END IF;
3415 
3416         if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3417 	       fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Applied receipt '||trx.trx_number||', Status: '||x_return_status);
3418         end if;
3419 
3420         write_debug_and_log('X_RETURN_STATUS=>'||X_RETURN_STATUS);
3421         write_debug_and_log('X_MSG_COUNT=>'||to_char(X_MSG_COUNT));
3422 
3423   END LOOP;
3424   ----------------------------------------------------------------------------------
3425   l_debug_info := 'Step 2: Apply debits against the receipt';
3426   ----------------------------------------------------------------------------------
3427 
3428     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3429        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
3430   end if;
3431 
3432   FOR trx in debit_trx_list
3433   LOOP
3434 
3435       if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3436        fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, 'Calling AR_RECEIPT_API_PUB.apply for debit trx: '
3437 	       || 'p_cash_receipt_id=' || p_cash_receipt_id || ','
3438 	       || 'trx.customer_trx_id=' || trx.customer_trx_id || ','
3439 	       || 'trx.payment_schedule_id=' || trx.payment_schedule_id || ','
3440 	       || 'trx.payment_amt=' || trx.payment_amt || ','
3441 	       || 'trx.service_charge='|| trx.service_charge || ','
3442 	       || 'trx.discount_amount=' || trx.discount_amount || ','
3443 	       || 'p_apply_date=' || To_Char(trunc(trx.receipt_date)) );
3444       end if;
3445 
3446     --
3447     -- Call the application API
3448     --
3449     AR_RECEIPT_API_PUB.apply(
3450         p_api_version           => 1.0,
3451         p_init_msg_list         => FND_API.G_TRUE,
3452         p_commit                => FND_API.G_FALSE,
3453         p_validation_level      => FND_API.G_VALID_LEVEL_FULL,
3454         x_return_status         => x_return_status,
3455         x_msg_count             => x_msg_count,
3456         x_msg_data              => x_msg_data,
3457         p_cash_receipt_id       => p_cash_receipt_id,
3458         p_customer_trx_id       => trx.customer_trx_id,
3459         p_applied_payment_schedule_id => trx.payment_schedule_id,
3460         p_amount_applied        => trx.payment_amt + nvl(trx.service_charge,0),
3461         p_discount              => trx.discount_amount,
3462         p_apply_date            => trunc(trx.receipt_date),
3463         p_called_from           => 'IREC'
3464         );
3465 
3466     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3467         fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Execution of AR_RECEIPT_API_PUB.apply is over. Return Status=' || x_return_status);
3468     end if;
3469 
3470     -- Check for errors and increment the count for
3471     -- errored applcations
3472     IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
3473       l_apply_err_count := l_apply_err_count + 1;
3474       p_apply_err_count := l_apply_err_count;
3475       p_return_status   := FND_API.G_RET_STS_ERROR;
3476       ROLLBACK TO ARI_Apply_Cash_Receipt_PVT;
3477       RETURN;
3478     END IF;
3479 
3480     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3481 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Applied Cash to '||trx.trx_number||' Status: '||x_return_status);
3482     end if;
3483 
3484     write_debug_and_log('X_RETURN_STATUS=>'||X_RETURN_STATUS);
3485     write_debug_and_log('X_MSG_COUNT=>'||to_char(X_MSG_COUNT));
3486 
3487   END LOOP;
3488 
3489   p_apply_err_count := l_apply_err_count;
3490   -- There are no errored applications; set the
3491   -- return status to success
3492   p_return_status := FND_API.G_RET_STS_SUCCESS;
3493 
3494     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3495     fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Exiting apply_cash with return status: '||p_return_status);
3496   end if;
3497 
3498 EXCEPTION
3499     WHEN OTHERS THEN
3500     	BEGIN
3501 	    p_return_status := FND_API.G_RET_STS_ERROR;
3502 
3503             write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
3504             write_debug_and_log('- Customer Id: '||p_customer_id);
3505             write_debug_and_log('- Customer Site Id: '||p_site_use_id);
3506             write_debug_and_log('- Cash Receipt Id: '||p_cash_receipt_id);
3507             write_debug_and_log('- Return Status: '||p_return_status);
3508             write_debug_and_log(SQLERRM);
3509 
3510             FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
3511             FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
3512             FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3513             FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
3514             FND_MSG_PUB.ADD;
3515         END;
3516 
3517 END apply_cash;
3518 
3519 
3520 /*=====================================================================
3521  | FUNCTION get_service_charge
3522  |
3523  | DESCRIPTION
3524  |   This function will calculate the service charge for the multiple
3525  |   invoices that have been selected for payment and return the
3526  |   total service charge that is to be applied.
3527  |
3528  | HISTORY
3529  |   26-APR-2004     vnb      Bug # 3467287 - Added Customer and Customer Site
3530  |							  as input parameters.
3531  |   19-JUL-2004     vnb      Bug # 2830823 - Added exception block to handle exceptions
3532  |   21-SEP-2004     vnb      Bug # 3886652 - Added customer site use id to ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE
3533  |
3534  +=====================================================================*/
3535  FUNCTION get_service_charge (  p_customer_id		    IN NUMBER,
3536                                 p_site_use_id          IN NUMBER DEFAULT NULL)
3537                              RETURN NUMBER IS
3538 
3539  l_invoice_list             ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE;
3540  l_total_service_charge     NUMBER;
3541  l_count                    NUMBER;
3542  l_currency_code            AR_IREC_PAYMENT_LIST_GT.currency_code%TYPE;
3543  l_service_charge           NUMBER;
3544 
3545  l_procedure_name           VARCHAR2(30);
3546  l_debug_info	 	    VARCHAR2(200);
3547 
3548  --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
3549  --Bug # 3886652 - Added customer site use id to ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE
3550  CURSOR invoice_list IS
3551    SELECT  payment_schedule_id,
3552            payment_amt as payment_amount,
3553            customer_id,
3554            customer_site_use_id,
3555            account_number,
3556            customer_trx_id,
3557            currency_code,
3558            service_charge
3559    FROM AR_IREC_PAYMENT_LIST_GT
3560    WHERE customer_id = p_customer_id
3561    AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
3562    AND trx_class IN ('INV','DM','CB','DEP');
3563 
3564  BEGIN
3565   --Assign default values
3566   l_total_service_charge := 0;
3567   l_procedure_name       :=  '.get_service_charge';
3568 
3569   SAVEPOINT service_charge_sp;
3570 
3571    ----------------------------------------------------------------------------------------
3572    l_debug_info := 'Check if service charge is enabled; else return zero';
3573    -----------------------------------------------------------------------------------------
3574    IF (PG_DEBUG = 'Y') THEN
3575        arp_standard.debug(l_debug_info);
3576    END IF;
3577    IF NOT (ARI_UTILITIES.is_service_charge_enabled(p_customer_id, p_site_use_id)) THEN
3578       RETURN l_total_service_charge;
3579    END IF;
3580 
3581    ----------------------------------------------------------------------------------------
3582    l_debug_info := 'Create the invoice list table';
3583    -----------------------------------------------------------------------------------------
3584    IF (PG_DEBUG = 'Y') THEN
3585        arp_standard.debug(l_debug_info);
3586    END IF;
3587 
3588    FOR invoice_rec in invoice_list
3589    LOOP
3590 
3591      --Bug 4071551 - Changed the indexing field to Payment Schedule Id from Customer Trx Id to keep uniqueness
3592      l_count := invoice_rec.payment_schedule_id;
3593 
3594      IF (PG_DEBUG = 'Y') THEN
3595        arp_standard.debug('Index: '||l_count);
3596      END IF;
3597 
3598      l_invoice_list(l_count).payment_schedule_id := invoice_rec.payment_schedule_id;
3599      l_invoice_list(l_count).payment_amount      := invoice_rec.payment_amount;
3600      l_invoice_list(l_count).customer_id         := invoice_rec.customer_id;
3601      --Bug # 3886652 - Added customer site use id to ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE
3602      l_invoice_list(l_count).customer_site_use_id:= invoice_rec.customer_site_use_id;
3603      l_invoice_list(l_count).account_number      := invoice_rec.account_number;
3604      l_invoice_list(l_count).customer_trx_id     := invoice_rec.customer_trx_id;
3605      l_invoice_list(l_count).currency_code       := invoice_rec.currency_code;
3606      l_invoice_list(l_count).service_charge      := invoice_rec.service_charge;
3607 
3608      l_currency_code := invoice_rec.currency_code;
3609 
3610    END LOOP;
3611 
3612    IF (PG_DEBUG = 'Y') THEN
3613        arp_standard.debug('End first Loop. Total records: '||l_invoice_list.COUNT);
3614    END IF;
3615 
3616    ----------------------------------------------------------------------------------------
3617    l_debug_info := 'Call the service charge package to compute';
3618    -----------------------------------------------------------------------------------------
3619    IF (PG_DEBUG = 'Y') THEN
3620        arp_standard.debug(l_debug_info);
3621    END IF;
3622    ARI_SERVICE_CHARGE_PKG.compute_service_charge(l_invoice_list);
3623 
3624    l_count := l_invoice_list.FIRST;
3625 
3626    WHILE l_count IS NOT NULL
3627    LOOP
3628      l_service_charge := ARI_UTILITIES.curr_round_amt(l_invoice_list(l_count).service_charge, l_currency_code);
3629 
3630      IF (PG_DEBUG = 'Y') THEN
3631        arp_standard.debug('Index: '|| l_count||' PaymentScheduleId: '||l_invoice_list(l_count).payment_schedule_id ||
3632                           'Service Charge: '||l_invoice_list(l_count).service_charge);
3633      END IF;
3634 
3635      ----------------------------------------------------------------------------------------
3636      l_debug_info := 'Update service charge in the Payment GT';
3637      -----------------------------------------------------------------------------------------
3638      IF (PG_DEBUG = 'Y') THEN
3639          arp_standard.debug(l_debug_info);
3640      END IF;
3641      UPDATE ar_irec_payment_list_gt
3642      SET    service_charge = l_service_charge
3643      WHERE  payment_schedule_id = l_invoice_list(l_count).payment_schedule_id;
3644 
3645      l_total_service_charge := l_total_service_charge + l_service_charge;
3646 
3647      -- Error handling required
3648      IF SQL%ROWCOUNT < 1 THEN
3649 	IF (PG_DEBUG = 'Y') THEN
3650 	   arp_standard.debug('Error - Cannot update '||l_count);
3651         END IF;
3652      END IF;
3653 
3654      l_count := l_invoice_list.NEXT(l_count);
3655 
3656    END LOOP;
3657 
3658    COMMIT;
3659 
3660    RETURN l_total_service_charge;
3661 
3662  EXCEPTION
3663     WHEN OTHERS THEN
3664     	BEGIN
3665             write_debug_and_log('Unexpected Exception while computing service charge');
3666             write_debug_and_log('- Customer Id: '||p_customer_id);
3667             write_debug_and_log('- Customer Site Id: '||p_site_use_id);
3668             write_debug_and_log('- Total Service charge: '||l_total_service_charge);
3669             write_debug_and_log(SQLERRM);
3670         END;
3671 
3672 	ROLLBACK TO service_charge_sp;
3673 
3674 	FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
3675         FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
3676         FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3677         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
3678         FND_MSG_PUB.ADD;
3679 
3680  END get_service_charge;
3681 
3682 /*=====================================================================
3683  | PROCEDURE apply_service_charge
3684  |
3685  | DESCRIPTION
3686  |   This function will calculate the service charge for the multiple
3687  |   invoices that have been selected for payment and return the
3688  |   total service charge that is to be applied.
3689  |
3690  | HISTORY
3691  |  26-APR-2004  vnb         Bug # 3467287 - Added Customer and Customer Site
3692  |                           as input parameters.
3693  |  19-JUL-2004  vnb         Bug # 2830823 - Added exception block to handle exceptions
3694  |  21-SEP-2004  vnb         Bug # 3886652 - Added customer site use id to ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE
3695  |
3696  +=====================================================================*/
3697  PROCEDURE apply_service_charge ( p_customer_id		    IN NUMBER,
3698                                   p_site_use_id         IN NUMBER DEFAULT NULL,
3699                                   x_return_status OUT NOCOPY VARCHAR2) IS
3700 
3701  l_invoice_list             ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE;
3702  l_total_service_charge     NUMBER;
3703  l_count                    NUMBER;
3704  l_return_status            VARCHAR2(2);
3705  l_procedure_name           VARCHAR2(50);
3706  l_debug_info	 	    VARCHAR2(200);
3707 
3708  --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
3709  --Bug # 3886652 - Added customer site use id to ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE
3710  CURSOR invoice_list IS
3711    SELECT  payment_schedule_id,
3712            payment_amt as payment_amount,
3713            customer_id,
3714            customer_site_use_id,
3715            account_number,
3716            customer_trx_id,
3717            currency_code,
3718            service_charge
3719    FROM AR_IREC_PAYMENT_LIST_GT
3720    WHERE customer_id = p_customer_id
3721     AND customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id), customer_site_use_id)
3722    AND ( trx_class = 'INV' OR
3723          trx_class = 'DM' OR
3724          trx_class = 'GUAR' OR
3725          trx_class = 'CB' OR
3726          trx_class = 'DEP'
3727 	   );
3728 
3729  BEGIN
3730    --Assign default values
3731    l_total_service_charge := 0;
3732    l_procedure_name := '.apply_service_charge';
3733 
3734    fnd_log_repository.init;
3735    if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3736 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'+');
3737    end if;
3738 
3739    l_count := 1;
3740 
3741    -- Create the invoice list table
3742    ----------------------------------------------------------------------------------
3743    l_debug_info := 'Create the invoice list table';
3744    ----------------------------------------------------------------------------------
3745    FOR invoice_rec in invoice_list
3746    LOOP
3747 
3748      --l_count := invoice_rec.customer_trx_id;
3749      --l_invoice_list.EXTEND;
3750      if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3751 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Index: '||l_count);
3752      end if;
3753      l_invoice_list(l_count).payment_schedule_id := invoice_rec.payment_schedule_id;
3754      l_invoice_list(l_count).payment_amount := invoice_rec.payment_amount;
3755      l_invoice_list(l_count).customer_id := invoice_rec.customer_id;
3756      --Bug # 3886652 - Added customer site use id to ARI_SERVICE_CHARGE_PKG.INVOICE_LIST_TABTYPE
3757      l_invoice_list(l_count).customer_site_use_id := invoice_rec.customer_site_use_id;
3758      l_invoice_list(l_count).account_number := invoice_rec.account_number;
3759      l_invoice_list(l_count).customer_trx_id := invoice_rec.customer_trx_id;
3760      l_invoice_list(l_count).currency_code := invoice_rec.currency_code;
3761      l_invoice_list(l_count).service_charge := invoice_rec.service_charge;
3762 
3763      l_count := l_count + 1;
3764    END LOOP;
3765 
3766    -- Call the service charge compute package
3767    ----------------------------------------------------------------------------------
3768    l_debug_info := 'Apply service charge';
3769    ----------------------------------------------------------------------------------
3770    l_return_status := ARI_SERVICE_CHARGE_PKG.apply_charge(l_invoice_list);
3771 
3772    IF ( l_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
3773      -- bug 3672530 - Ensure graceful error handling
3774      x_return_status := FND_API.G_RET_STS_ERROR;
3775      if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3776 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'ERROR: Loop count is: '||l_count);
3777      end if;
3778      APP_EXCEPTION.RAISE_EXCEPTION;
3779    END IF;
3780 
3781    if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3782 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'-');
3783    end if;
3784 
3785  EXCEPTION
3786     WHEN OTHERS THEN
3787     	BEGIN
3788 	    x_return_status := FND_API.G_RET_STS_ERROR;
3789 
3790             write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
3791             write_debug_and_log('- Customer Id: '||p_customer_id);
3792             write_debug_and_log('- Customer Site Id: '||p_site_use_id);
3793             write_debug_and_log('- Total Service charge: '||l_total_service_charge);
3794             write_debug_and_log('- Return Status: '||l_return_status);
3795             write_debug_and_log(SQLERRM);
3796 
3797             FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
3798             FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
3799             FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
3800             FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
3801             FND_MSG_PUB.ADD;
3802         END;
3803 
3804 END apply_service_charge;
3805 
3806 
3807  /*==============================================================
3808  | PROCEDURE  pay_multiple_invoices
3809  |
3810  | DESCRIPTION Used to make paymnets from iRec UI
3811  |
3812  | PARAMETERS  Lots
3813  |
3814  | KNOWN ISSUES
3815  |
3816  | NOTES
3817  | p_cc_bill_to_site_id value is sent as 0 when OIR_VERIFY_CREDIT_CARD_DETAILS profile is NONE or SECURITY_CODE for both New  Credit Cards
3818  | p_cc_bill_to_site_id value is sent as -1 when OIR_VERIFY_CREDIT_CARD_DETAILS is either BOTH or ADDRESS and for New Credit Card  Accounts
3819  | p_cc_bill_to_site_id value is sent as CC bill site id when OIR_VERIFY_CREDIT_CARD_DETAILS profile is either BOTH or ADDRESS for Saved Credit Cards
3820  |
3821  | MODIFICATION HISTORY
3822  | Date          Author       Description of Changes
3823  | 13-Jan-2003   krmenon      Created
3824  | 21-OCT-2004   vnb          Bug 3944029 - Modified pay_multiple_invoices to pass
3825  |							  correct site_use_id to other APIs
3826  | 03-NOV-2004   vnb          Bug 3335944 - One Time Credit Card Verification
3827  | 18-Oct-2005	 rsinthre     Bug 4673563 - Error making credit card payment
3828  +==============================================================*/
3829 
3830  PROCEDURE pay_multiple_invoices(p_payment_amount      IN NUMBER,
3831                                 p_discount_amount     IN NUMBER,
3832                                 p_customer_id         IN NUMBER,
3833                                 p_site_use_id         IN NUMBER,
3834                                 p_account_number      IN VARCHAR2,
3835                                 p_expiration_date     IN DATE,
3836                                 p_account_holder_name IN VARCHAR2,
3837                                 p_account_type        IN VARCHAR2,
3838                                 p_payment_instrument  IN VARCHAR2,
3839                                 p_address_line1       IN VARCHAR2 default null,
3840                                 p_address_line2       IN VARCHAR2 default null,
3841                                 p_address_line3       IN VARCHAR2 default null,
3842                                 p_address_city        IN VARCHAR2 default null,
3843                                 p_address_county      IN VARCHAR2 default null,
3844                                 p_address_state       IN VARCHAR2 default null,
3845                                 p_address_country     IN VARCHAR2 default null,
3846                                 p_address_postalcode  IN VARCHAR2 default null,
3847                                 p_cvv2                IN NUMBER,
3848                                 p_bank_branch_id      IN NUMBER,
3849                                 p_receipt_date        IN DATE DEFAULT trunc(SYSDATE),
3850                                 p_new_account_flag    IN VARCHAR2 DEFAULT 'FALSE',
3851 					  p_receipt_site_id     IN NUMBER,
3852 				p_bank_id	      IN NUMBER,
3853 				p_card_brand	      IN VARCHAR2,
3854 				p_cc_bill_to_site_id  IN NUMBER,
3855 				p_single_use_flag     IN VARCHAR2 default 'N',
3856 				p_iban		      IN VARCHAR2,
3857 				p_instr_assign_id     IN NUMBER default 0,
3858 				p_bank_account_id     IN OUT NOCOPY NUMBER,
3859                                 p_cash_receipt_id     OUT NOCOPY NUMBER,
3860                                 p_status              OUT NOCOPY VARCHAR2,
3861                                 x_msg_count           OUT NOCOPY NUMBER,
3862                                 x_msg_data            OUT NOCOPY VARCHAR2
3863                                 ) IS
3864   -- =================================
3865   -- DECLARE ALL LOCAL VARIABLES HERE
3866   -- =================================
3867   l_receipt_currency_code       AR_CASH_RECEIPTS_ALL.CURRENCY_CODE%TYPE;
3868   l_receipt_exchange_rate       AR_CASH_RECEIPTS_ALL.EXCHANGE_RATE%TYPE;
3869   l_receipt_exchange_rate_type  AR_CASH_RECEIPTS_ALL.EXCHANGE_RATE_TYPE%TYPE;
3870   l_receipt_exchange_rate_date  DATE;
3871 
3872   l_invoice_exchange_rate       AR_PAYMENT_SCHEDULES_ALL.EXCHANGE_RATE%TYPE;
3873   l_receipt_method_id           AR_CASH_RECEIPTS_ALL.RECEIPT_METHOD_ID%TYPE;
3874   l_remit_bank_account_id       AR_CASH_RECEIPTS_ALL.REMIT_BANK_ACCT_USE_ID%TYPE;
3875   l_receipt_creation_status     VARCHAR2(80);
3876   l_site_use_id                 NUMBER(15);
3877   l_bank_account_id 	        NUMBER;
3878   l_bank_account_uses_id        NUMBER;
3879   l_cvv2                        iby_fndcpt_tx_extensions.instrument_security_code%TYPE;
3880 
3881   l_invoice_trx_number          AR_PAYMENT_SCHEDULES_ALL.TRX_NUMBER%TYPE;
3882   l_cr_id                       AR_CASH_RECEIPTS_ALL.CASH_RECEIPT_ID%TYPE;
3883   x_return_status               VARCHAR2(100);
3884   l_msg_count                   NUMBER;
3885   l_msg_data                    VARCHAR2(4000);
3886 
3887   l_call_payment_processor      VARCHAR2(1);
3888   l_response_error_code         VARCHAR2(80);
3889   l_bank_branch_id	        CE_BANK_ACCOUNTS.BANK_BRANCH_ID%TYPE;
3890   l_apply_err_count             NUMBER;
3891   p_payment_schedule_id         NUMBER;
3892 
3893   l_create_credit_card		IBY_FNDCPT_SETUP_PUB.CreditCard_rec_type;
3894   l_result_rec_type		IBY_FNDCPT_COMMON_PUB.Result_rec_type;
3895   l_procedure_name VARCHAR2(30);
3896 
3897   l_debug_info	 	        VARCHAR2(200);
3898 
3899     l_payer_rec			IBY_FNDCPT_COMMON_PUB.PayerContext_rec_type;
3900     l_trxn_rec			IBY_FNDCPT_TRXN_PUB.TrxnExtension_rec_type;
3901     l_payee_rec         IBY_FNDCPT_TRXN_PUB.PayeeContext_rec_type;
3902     l_result_rec		IBY_FNDCPT_COMMON_PUB.Result_rec_type;
3903     l_payment_channel_code	IBY_FNDCPT_PMT_CHNNLS_B.PAYMENT_CHANNEL_CODE%TYPE;
3904 
3905     l_cc_location_rec		HZ_LOCATION_V2PUB.LOCATION_REC_TYPE;
3906     l_cc_bill_to_site_id	NUMBER;
3907 
3908     l_extn_id number;
3909     l_payer_party_id  NUMBER;
3910 
3911    l_payment_server_order_num VARCHAR2(80);
3912        l_instr_assign_id number;
3913 
3914     l_cvv_use           VARCHAR2(100);
3915     l_billing_addr_use  VARCHAR2(100);
3916   CURSOR party_id_cur IS
3917     SELECT PARTY_ID FROM HZ_CUST_ACCOUNTS WHERE CUST_ACCOUNT_ID = p_customer_id;
3918 
3919     party_id_rec		party_id_cur%ROWTYPE;
3920 
3921     p_site_use_id_srvc_chrg NUMBER;
3922 
3923 BEGIN
3924   --Assign default values
3925 
3926   l_receipt_currency_code  := 'USD';
3927   l_call_payment_processor := FND_API.G_TRUE;
3928   l_apply_err_count        := 0;
3929   x_msg_count              := 0;
3930   x_msg_data               := '';
3931   l_procedure_name         := '.pay_multiple_invoices';
3932 
3933 
3934   fnd_log_repository.init;
3935 
3936    --------------------------------------------------------------------
3937   l_debug_info := 'In debug mode, log we have entered this procedure';
3938   --------------------------------------------------------------------
3939   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3940 	  fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,
3941                  'Begin+');
3942 	  fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,
3943                  'p_payment_amount ' ||p_payment_amount ||
3944                  'p_discount_amount ' ||p_discount_amount ||
3945                  'p_customer_id ' || p_customer_id ||
3946                  'p_site_use_id ' ||p_site_use_id ||
3947                  'p_account_number ' ||p_account_number ||
3948                  'p_expiration_date ' ||p_expiration_date ||
3949                  'p_account_holder_name ' ||p_account_holder_name ||
3950                  'p_account_type ' || p_account_type ||
3951                  'p_payment_instrument ' || p_payment_instrument ||
3952                  'p_bank_branch_id ' ||p_bank_branch_id ||
3953                  'p_new_account_flag ' ||p_new_account_flag ||
3954                  'p_receipt_date ' ||p_receipt_date ||
3955                  'p_bank_account_id ' ||p_bank_account_id );
3956   end if;
3957 
3958   -- IF Customer Site Use Id is -1 then it is to be set as null
3959   IF ( p_site_use_id = -1 ) THEN
3960     l_site_use_id := NULL;
3961   ELSE
3962     l_site_use_id := p_site_use_id;
3963   END IF;
3964 
3965   IF p_cvv2 = 0 AND p_payment_instrument = 'BANK_ACCOUNT' THEN
3966    l_cvv2 := NULL;
3967   else
3968    l_cvv2 := p_cvv2;
3969   END IF;
3970 
3971 
3972   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
3973 	  fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,
3974                  'Calling get_payment_information');
3975   end if;
3976 
3977 
3978   ---------------------------------------------------------------------------
3979   l_debug_info := 'Get the Payment Schedule Id if there is only one invoice';
3980   ---------------------------------------------------------------------------
3981   BEGIN
3982     select payment_schedule_id into p_payment_schedule_id
3983     from AR_IREC_PAYMENT_LIST_GT
3984     where customer_id = p_customer_id
3985     and customer_site_use_id = nvl(l_site_use_id, customer_site_use_id);
3986     EXCEPTION
3987       when others then
3988         IF (PG_DEBUG = 'Y') THEN
3989           arp_standard.debug('There may be multiple invoices for payment');
3990         END IF;
3991   END;
3992 
3993   ---------------------------------------------------------------------------
3994   l_debug_info := 'Call get_payment_information';
3995   ---------------------------------------------------------------------------
3996 
3997   get_payment_information(
3998           p_customer_id             => p_customer_id,
3999           p_site_use_id             => l_site_use_id,
4000           p_payment_schedule_id     => p_payment_schedule_id,
4001           p_payment_instrument      => p_payment_instrument,
4002           p_trx_date                => trunc(p_receipt_date),
4003           p_currency_code           => l_receipt_currency_code,
4004           p_exchange_rate           => l_invoice_exchange_rate,
4005           p_receipt_method_id       => l_receipt_method_id,
4006           p_remit_bank_account_id   => l_remit_bank_account_id,
4007           p_receipt_creation_status => l_receipt_creation_status,
4008           p_trx_number              => l_invoice_trx_number,
4009 	  p_payment_channel_code    => l_payment_channel_code);
4010 
4011   --DEBUG
4012   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4013 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_rct_curr => ' || l_receipt_currency_code);
4014 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_rct_method_id => ' ||l_receipt_method_id );
4015 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_remit_bank_account_id => ' || l_Remit_bank_account_id);
4016 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_receipt_creation_status => ' || l_receipt_creation_status );
4017 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_site_use_id => ' || l_site_use_id );
4018 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_receipt_currency_code => ' || l_receipt_currency_code);
4019   end if;
4020 
4021  IF p_payment_instrument = 'CREDIT_CARD' THEN
4022 	  get_payment_channel_attribs
4023 	  (
4024 		  p_channel_code 	   => 'CREDIT_CARD',
4025 		  x_return_status    => x_return_status,
4026 		  x_cvv_use 	       => l_cvv_use,
4027 		  x_billing_addr_use => l_billing_addr_use,
4028 		  x_msg_count 	     => x_msg_count,
4029 		  x_msg_data 	       => x_msg_data
4030 	  );
4031 	    IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4032 
4033 		  if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4034 			  fnd_log.string(fnd_log.LEVEL_STATEMENT,
4035 				  G_PKG_NAME||l_procedure_name,
4036 				  'ERROR IN GETTING IBY PAYMENT CHANNEL ATTRIBUTES');
4037 		  end if;
4038 
4039 		  x_return_status := FND_API.G_RET_STS_ERROR;
4040 		  write_error_messages(x_msg_data, x_msg_count);
4041 		  RETURN;
4042     	   END IF;
4043 
4044 END IF;
4045 
4046   -- If the payment instrument is a bank account then
4047   -- set the bank branch id
4048   IF (p_payment_instrument = 'BANK_ACCOUNT') THEN
4049       l_bank_branch_id := p_bank_branch_id;
4050   ELSE
4051       l_bank_branch_id := null;
4052   END IF;
4053 
4054   --KRMENON DEBUG
4055 IF (l_receipt_currency_code IS NULL OR '' = l_receipt_currency_code) THEN
4056     --Bug2925392: Get Currency from AR_IREC_PAYMENT_LIST_GT. All records will have same currency.
4057     --Bug # 3467287 - The Global Temp table must be striped by Customer and Customer Site.
4058     ---------------------------------------------------------------------------
4059     l_debug_info := 'If the currency code is not set yet, get the currency code';
4060     ---------------------------------------------------------------------------
4061     BEGIN
4062       select currency_code into l_receipt_currency_code
4063       from AR_IREC_PAYMENT_LIST_GT
4064       where customer_id = p_customer_id
4065       and customer_site_use_id = nvl(l_site_use_id, customer_site_use_id);
4066       --group by currency_code;
4067       EXCEPTION
4068         when others then
4069           IF (PG_DEBUG = 'Y') THEN
4070             arp_standard.debug('Error getting currency code');
4071           END IF;
4072     END;
4073   END IF;
4074 
4075   SAVEPOINT ARI_Create_Cash_PVT;
4076 
4077 	OPEN party_id_cur;
4078 	FETCH party_id_cur INTO party_id_rec;
4079 	IF(party_id_cur%FOUND) THEN
4080 		l_payer_party_id := party_id_rec.party_id;
4081 	END IF;
4082 	CLOSE party_id_cur;
4083 
4084 	l_cc_bill_to_site_id			:= p_cc_bill_to_site_id;
4085 	l_cc_location_rec.country		:= p_address_country;
4086 	l_cc_location_rec.address1		:= p_address_line1;
4087 	l_cc_location_rec.address2		:= p_address_line2;
4088 	l_cc_location_rec.address3		:= p_address_line3;
4089 	l_cc_location_rec.city			:= p_address_city;
4090 	l_cc_location_rec.postal_code		:= p_address_postalcode;
4091 	l_cc_location_rec.state			:= p_address_state;
4092 	l_cc_location_rec.county		:= p_address_county;
4093 	l_cc_location_rec.created_by_module	:= 'ARI';
4094 
4095 	IF(p_payment_instrument = 'CREDIT_CARD') and l_cc_bill_to_site_id = -1 THEN
4096       IF(l_billing_addr_use = 'REQUIRED') THEN
4097 		create_cc_bill_to_site(
4098 			p_init_msg_list		=> FND_API.G_FALSE,
4099 			p_commit		=> FND_API.G_FALSE,
4100 			p_cc_location_rec	=> l_cc_location_rec,
4101 			p_payer_party_id	=> l_payer_party_id,
4102 			x_cc_bill_to_site_id	=> l_cc_bill_to_site_id,
4103 			x_return_status		=> x_return_status,
4104 			x_msg_count		=> l_msg_count,
4105 			x_msg_data		=> l_msg_data);
4106 
4107 		 IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4108 
4109 		      if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4110 			      fnd_log.string(fnd_log.LEVEL_STATEMENT,
4111 				      G_PKG_NAME||l_procedure_name,
4112 				      'ERROR IN CREATING PAYMENT INSTRUMENT');
4113 		      end if;
4114 
4115 		      p_status := FND_API.G_RET_STS_ERROR;
4116 		      ROLLBACK TO ARI_Create_Cash_PVT;
4117 		      write_error_messages(x_msg_data, x_msg_count);
4118 		      RETURN;
4119 		 END IF;
4120       END IF;
4121 	 END IF;	--p_payment_instrument
4122 
4123 
4124 
4125 
4126   IF ( p_new_account_flag = 'TRUE' ) THEN
4127   -- Now create a payment instrument
4128     ---------------------------------------------------------------------------
4129     l_debug_info := 'Create a payment instrument';
4130     ---------------------------------------------------------------------------
4131     create_payment_instrument ( p_customer_id         => p_customer_id,
4132 				p_customer_site_id    => l_site_use_id,
4133 				p_account_number      => p_account_number,
4134 				p_payer_party_id      => l_payer_party_id,
4135 				p_expiration_date     => p_expiration_date,
4136 				p_account_holder_name => p_account_holder_name,
4137 				p_account_type        => p_account_type,
4138 				p_payment_instrument  => p_payment_instrument,
4139 				p_address_country     => p_address_country,
4140 				p_bank_branch_id      => p_bank_branch_id,
4141 				p_receipt_curr_code   => l_receipt_currency_code,
4142 				p_status              => x_return_status,
4143 				x_msg_count           => l_msg_count,
4144 				x_msg_data            => l_msg_data,
4145 				p_bank_id	      => p_bank_id,
4146 				p_card_brand	      => p_card_brand,
4147 				p_cc_bill_to_site_id  => l_cc_bill_to_site_id,
4148 				p_single_use_flag     => p_single_use_flag,
4149 				p_iban		      => p_iban,
4150 				p_assignment_id       => l_instr_assign_id,
4151 				p_bank_account_id   => p_bank_account_id) ;
4152 
4153 
4154     -- Check if the payment instrument was created successfully
4155     IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4156       if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4157 	      fnd_log.string(fnd_log.LEVEL_STATEMENT,
4158                       G_PKG_NAME||l_procedure_name,
4159                       'ERROR IN CREATING PAYMENT INSTRUMENT');
4160       end if;
4161 
4162       p_status := FND_API.G_RET_STS_ERROR;
4163       write_error_messages(x_msg_data, x_msg_count);
4164       ROLLBACK TO ARI_Create_Cash_PVT;
4165       RETURN;
4166     ELSE
4167     	-- When payment instrument is created successfully
4168     	IF ( ARI_UTILITIES.save_payment_instrument_info(p_customer_id, l_site_use_id) ) THEN
4169 	    -- If iRec set up is not to save CC then, if update of CC fails we should roll back even create.
4170 	    -- So here the commit flag is controlled by that profile
4171 	    commit;
4172  	END IF;
4173     END IF;
4174 
4175   ELSE
4176     l_bank_account_id := p_bank_account_id;
4177     l_instr_assign_id := p_instr_assign_id;
4178   END IF;
4179 
4180 
4181   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4182 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Done with bank Creation .....');
4183 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Expiration date for bank account: ' || p_expiration_date);
4184 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Bank Acct Id: '||l_bank_account_id);
4185 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Bank Acct Uses Id: '||l_bank_account_uses_id);
4186   end if;
4187 
4188   /*------------------------------------+
4189    | Standard start of API savepoint    |
4190    +------------------------------------*/
4191  IF ( ARI_UTILITIES.save_payment_instrument_info(p_customer_id, p_site_use_id) ) THEN
4192 	  SAVEPOINT ARI_Create_Cash_PVT;
4193  END IF;
4194   -----------------------------------------------------------------------------------------
4195   l_debug_info := 'Call public IBY API - create TRANSACTION EXTENSION';
4196   -----------------------------------------------------------------------------------------
4197 
4198         l_payer_rec.payment_function:='CUSTOMER_PAYMENT';
4199         l_payer_rec.Cust_Account_Id:=p_customer_id;
4200         l_payer_rec.Account_Site_Id:=l_site_use_id;
4201         l_payer_rec.PARTY_ID := l_payer_party_id;
4202         if l_site_use_id is not null then
4203 	        l_payer_rec.org_type:= 'OPERATING_UNIT';
4204 	        l_payer_rec.org_id:= mo_global.get_current_org_id;
4205         else
4206              l_payer_rec.org_type:= NULL;
4207 	        l_payer_rec.org_id:= NULL;
4208         end if;
4209 	l_payee_rec.org_type := 'OPERATING_UNIT';
4210 	l_payee_rec.org_id := mo_global.get_current_org_id ;
4211 
4212         select 'ARI_'||ar_payment_server_ord_num_s.nextval
4213         into l_payment_server_order_num
4214         from dual;
4215 
4216         l_trxn_rec.Originating_Application_Id:=222;
4217         l_trxn_rec.Order_Id:=l_payment_server_order_num;
4218         l_trxn_rec.Instrument_Security_Code :=l_cvv2;
4219         -- Debug message
4220         write_debug_and_log('l_payment_channel_code'||l_payment_channel_code);
4221         write_debug_and_log('l_instr_assign_id'||l_instr_assign_id);
4222         write_debug_and_log('l_payment_server_order_num'||l_payment_server_order_num);
4223 
4224         IBY_FNDCPT_TRXN_PUB.Create_Transaction_Extension
4225                           (
4226 			    p_api_version	=>1.0,
4227 			    p_init_msg_list	=>FND_API.G_TRUE,
4228 			    p_commit		=> FND_API.G_FALSE,
4229          		    x_return_status	=>x_return_status,
4230 		            x_msg_count		=>l_msg_count,
4231 		            x_msg_data		=> l_msg_data,
4232 			    p_payer		=> l_payer_rec,
4233 			    p_pmt_channel	=> l_payment_channel_code,
4234 			    p_instr_assignment	=>l_instr_assign_id,
4235 			    p_trxn_attribs	=> l_trxn_rec,
4236 			    x_entity_id		=> l_extn_id,
4237 			    x_response		=> l_result_rec);
4238 
4239       IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4240 	      if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4241 		      fnd_log.string(fnd_log.LEVEL_STATEMENT,
4242 			      G_PKG_NAME||l_procedure_name,
4243 			      'ERROR IN CREATING TRANSACTION EXTENSION');
4244 		  fnd_log.string(fnd_log.LEVEL_STATEMENT,
4245 			      G_PKG_NAME||l_procedure_name,l_result_rec.result_code);
4246 	      end if;
4247 
4248 	      x_msg_count := x_msg_count + l_msg_count;
4249 	      if (l_msg_data is not null) then
4250 		    x_msg_data  := x_msg_data || l_msg_data || '*';
4251 	      end if;
4252 
4253 	      x_msg_data := x_msg_data || '*' || l_result_rec.result_code;
4254 	      p_status := FND_API.G_RET_STS_ERROR;
4255 	      ROLLBACK TO ARI_Create_Cash_PVT;
4256 	      write_error_messages(x_msg_data, x_msg_count);
4257 	      RETURN;
4258     END IF;
4259 
4260   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4261 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Done with create trxn extn.....');
4262 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_extn_id : ' ||l_extn_id);
4263   end if;
4264   write_debug_and_log('l_receipt_currency_code : ' || l_receipt_currency_code);
4265   write_debug_and_log('l_invoice_exchange_rate : ' || to_char(l_invoice_exchange_rate));
4266   write_debug_and_log('l_extn_id : ' || l_extn_id);
4267 
4268   ---------------------------------------------------------------------------
4269   l_debug_info := 'Call get_exchange_rate';
4270   ---------------------------------------------------------------------------
4271   get_exchange_rate( p_trx_currency_code      => l_receipt_currency_code,
4272                      p_trx_exchange_rate      => l_invoice_exchange_rate,
4273                      p_def_exchange_rate_date => trunc(SYSDATE),
4274                      p_exchange_rate          => l_receipt_exchange_rate,
4275                      p_exchange_rate_type     => l_receipt_exchange_rate_type,
4276                      p_exchange_rate_date     => l_receipt_exchange_rate_date);
4277 
4278 if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4279 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Done with getexchangerate.....');
4280 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_receipt_currency_code : ' || l_receipt_currency_code);
4281 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'l_receipt_exchange_rate : ' || to_char(l_invoice_exchange_rate));
4282   end if;
4283 
4284   -- for demo purposes only: if fnd function ARIPAYMENTDEMOMODE
4285   -- is added to the menu of the current responsibility, supress
4286   -- call to iPayment after the receipt creation.
4287 
4288  /*------------------------------------------------------+
4289   | For credit cards iPayment is called to authorize and |
4290   | capture the payment. For bank account transfers      |
4291   | iPayment is called in receivables remittance process |
4292   +------------------------------------------------------*/
4293   IF (fnd_function.test('ARIPAYMENTDEMOMODE')
4294      OR p_payment_instrument = 'BANK_ACCOUNT') THEN /* J Rautiainen ACH Implementation */
4295     l_call_payment_processor := FND_API.G_FALSE;
4296   ELSE
4297     l_call_payment_processor := FND_API.G_TRUE;
4298   END IF;
4299 
4300   IF (p_receipt_site_id <> -1) THEN
4301     l_site_use_id := p_receipt_site_id;
4302   END IF;
4303 
4304   -- Now create a cash receipt
4305   ---------------------------------------------------------------------------
4306   l_debug_info := 'Create a cash receipt: Call create_receipt';
4307   ---------------------------------------------------------------------------
4308   create_receipt (p_payment_amount		=> p_payment_amount,
4309                   p_customer_id			=> p_customer_id,
4310                   p_site_use_id			=> l_site_use_id,
4311                   p_bank_account_id		=> l_bank_account_id,
4312                   p_receipt_date		=> trunc(p_receipt_date),
4313                   p_receipt_method_id		=> l_receipt_method_id,
4314                   p_receipt_currency_code	=> l_receipt_currency_code,
4315                   p_receipt_exchange_rate	=> l_receipt_exchange_rate,
4316                   p_receipt_exchange_rate_type	=> l_receipt_exchange_rate_type,
4317                   p_receipt_exchange_rate_date	=> l_receipt_exchange_rate_date,
4318                   p_trxn_extn_id		=> l_extn_id,
4319                   p_cash_receipt_id		=> p_cash_receipt_id,
4320                   p_status			=> x_return_status,
4321                   x_msg_count			=> l_msg_count,
4322                   x_msg_data			=> l_msg_data
4323                  );
4324 
4325   arp_standard.debug('create receipt -->  ' || x_return_status || 'receipt id --> ' || p_cash_receipt_id);
4326   arp_standard.debug('X_RETURN_STATUS=>'||X_RETURN_STATUS);
4327 
4328   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4329 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Done with receipt creation ....');
4330 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Return Status: '||x_return_status);
4331 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Cash Receipt Id: '||to_char(p_cash_receipt_id));
4332 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Bank Account Id: '||to_char(p_bank_account_id));
4333   end if;
4334 
4335   -- Check for error in receipt creation. If it is an error
4336   -- the rollback and return.
4337   IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS OR p_cash_receipt_id IS NULL ) THEN
4338     --Bug 3672530 - Error handling
4339     p_status := FND_API.G_RET_STS_ERROR;
4340     ROLLBACK TO ARI_Create_Cash_PVT;
4341     write_error_messages(x_msg_data, x_msg_count);
4342     RETURN;
4343   END IF;
4344 
4345   p_site_use_id_srvc_chrg := p_site_use_id;
4346   IF (p_receipt_site_id <> -1) THEN
4347     p_site_use_id_srvc_chrg := p_receipt_site_id;
4348   END IF;
4349 
4350   -- If service charge has been enabled, adjust the invoice
4351   -- with the service charge
4352   -- Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.is_service_charge_enabled
4353   IF ( ARI_UTILITIES.is_service_charge_enabled(p_customer_id, p_site_use_id_srvc_chrg) ) THEN
4354     ---------------------------------------------------------------------------------
4355     l_debug_info := 'Service charge enabled: adjust the invoice with service charge';
4356     ---------------------------------------------------------------------------------
4357     apply_service_charge(p_customer_id, l_site_use_id, x_return_status);
4358     IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
4359       --Bug 3672530 - Error handling
4360       p_status := FND_API.G_RET_STS_ERROR;
4361       ROLLBACK TO ARI_Create_Cash_PVT;
4362       write_error_messages(x_msg_data, x_msg_count);
4363       RETURN;
4364     END IF;
4365   END IF;
4366 
4367    --Bug 8239939 , 6026781: All locations project. Reset the site_use_id to actual value
4368  --when navigating from All Locations or My All Locations
4369   IF (p_receipt_site_id <> -1) THEN
4370     l_site_use_id := p_site_use_id;
4371   END IF;
4372 
4373 
4374   -- If the cash receipt has been created successfully then
4375   -- apply the receipt to the transactions selected
4376   ---------------------------------------------------------------------------------
4377   l_debug_info := 'Apply the receipt to the transactions selected:call apply_cash';
4378   ---------------------------------------------------------------------------------
4379   apply_cash( p_customer_id     => p_customer_id,
4380               p_site_use_id     => l_site_use_id,
4381               p_cash_receipt_id => p_cash_receipt_id,
4382               p_return_status   => x_return_status,
4383               p_apply_err_count => l_apply_err_count,
4384               x_msg_count       => l_msg_count,
4385               x_msg_data        => l_msg_data
4386             );
4387 
4388   -- Check if any of the applications errored out
4389   -- If so the rollback everything and return
4390   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4391 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Apply Cash call ended with Status : '||x_return_status);
4392   end if;
4393 
4394   IF ( l_apply_err_count > 0 ) THEN
4395     x_msg_count := x_msg_count + l_msg_count;
4396     if (l_msg_data is not null) then
4397 	    x_msg_data  := x_msg_data || l_msg_data || '*';
4398     end if;
4399     p_status := FND_API.G_RET_STS_ERROR;
4400     ROLLBACK TO ARI_Create_Cash_PVT;
4401     write_error_messages(x_msg_data, x_msg_count);
4402     RETURN;
4403   END IF;
4404 
4405   -- Seems like all is fine. So we shall go ahead and
4406   -- do the final task of capturing the CC payment
4407   -- only if it is a credit card payment
4408   IF (p_payment_instrument = 'CREDIT_CARD' AND
4409       l_call_payment_processor = FND_API.G_TRUE) THEN
4410 
4411     if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4412 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Calling process_payment .....');
4413     end if;
4414     --------------------------------------------------------------------
4415     l_debug_info := 'Capture Credit Card payment';
4416     --------------------------------------------------------------------
4417     process_payment(p_cash_receipt_id     => p_cash_receipt_id,
4418                     p_payer_rec		  => l_payer_rec,
4419                     p_payee_rec           => l_payee_rec,
4420                     p_called_from         => 'IREC',
4421                     p_response_error_code => l_response_error_code,
4422                     x_msg_count           => l_msg_count,
4423                     x_msg_data            => l_msg_data,
4424                     x_return_status       => x_return_status);
4425 
4426    if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4427 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Process Payment ended with Status : '||x_return_status);
4428 	fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Response Code: '|| l_response_error_code);
4429     end if;
4430     -- If the payment processor call fails, then we need to rollback all the changes
4431     -- made in the create() and apply() routines also.
4432     IF x_return_status <> FND_API.G_RET_STS_SUCCESS THEN
4433 	 x_msg_count := x_msg_count + l_msg_count;
4434 	 if (l_msg_data is not null) then
4435 		    x_msg_data  := x_msg_data || l_msg_data || '*';
4436 	 end if;
4437 
4438 	  x_msg_data := x_msg_data || '*' || l_result_rec.result_code;
4439       --Bug 3672530 - Error handling
4440       p_status := FND_API.G_RET_STS_ERROR;
4441       ROLLBACK TO ARI_Create_Cash_PVT;
4442       write_error_messages(x_msg_data, x_msg_count);
4443       RETURN; -- exit back to caller
4444     END IF;
4445 
4446   END IF; -- END PROCESS_PAYMENT CALL
4447   -- Now that we have successfully captured the payment
4448   -- erase the CC info if setup says not to store this
4449   -- info
4450   -- Bug 3886652 - Customer and Customer Site added to ARI_CONFIG APIs
4451   --               to add flexibility in configuration.
4452   IF NOT ( ARI_UTILITIES.save_payment_instrument_info(p_customer_id, p_site_use_id) ) THEN
4453 
4454     ---------------------------------------------------------------------------------------------------------
4455     l_debug_info := 'Payment instrument information not to be stored, erase the CC information after payment';
4456     ---------------------------------------------------------------------------------------------------------
4457           l_create_credit_card.Card_Id                   := l_bank_account_id;
4458 	  l_create_credit_card.Active_Flag               := 'N';
4459 	  l_create_credit_card.Inactive_Date             := TRUNC(SYSDATE - 1);
4460           l_create_credit_card.single_use_flag           := 'Y';
4461 
4462 	IBY_FNDCPT_SETUP_PUB.Update_Card
4463             (
4464             p_api_version      => 1.0,
4465             p_init_msg_list    => FND_API.G_TRUE,
4466             p_commit           => FND_API.G_FALSE,
4467             x_return_status    => x_return_status,
4468             x_msg_count        => l_msg_count,
4469             x_msg_data         => l_msg_data,
4470             p_card_instrument  => l_create_credit_card,
4471             x_response         => l_result_rec_type
4472             );
4473 
4474 	IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4475 	 p_status := FND_API.G_RET_STS_ERROR;
4476 	 x_msg_count := x_msg_count + l_msg_count;
4477 	 if (l_msg_data is not null) then
4478 		    x_msg_data  := x_msg_data || l_msg_data || '*';
4479 	 end if;
4480 	 x_msg_data := x_msg_data || '*' || l_result_rec.result_code;
4481 	 ROLLBACK TO ARI_Create_Cash_PVT;
4482 	 write_error_messages(x_msg_data, x_msg_count);
4483 	 RETURN;
4484 	END IF;
4485   ELSE
4486  	IF ( p_new_account_flag = 'FALSE' AND p_payment_instrument = 'CREDIT_CARD' ) THEN
4487 		l_create_credit_card.Card_Id                   := l_bank_account_id;
4488 		l_create_credit_card.single_use_flag           := 'N';
4489 	        l_create_credit_card.Card_Holder_Name          := p_account_holder_name;
4490 
4491     IF(l_billing_addr_use = 'REQUIRED') THEN
4492       IF(l_cc_bill_to_site_id <> 0 AND l_cc_bill_to_site_id <> -1) THEN
4493         l_create_credit_card.Billing_Address_Id        := l_cc_bill_to_site_id;
4494       END IF;
4495     END IF;
4496 
4497 		IBY_FNDCPT_SETUP_PUB.Update_Card
4498 		(
4499 			p_api_version      => 1.0,
4500 			p_init_msg_list    => FND_API.G_TRUE,
4501 			p_commit           => FND_API.G_FALSE,
4502 			x_return_status    => x_return_status,
4503 			x_msg_count        => l_msg_count,
4504 			x_msg_data         => l_msg_data,
4505 			p_card_instrument  => l_create_credit_card,
4506 			x_response         => l_result_rec_type
4507 		);
4508 
4509 	        IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4510 		        p_status := FND_API.G_RET_STS_ERROR;
4511 		        x_msg_count := x_msg_count + l_msg_count;
4512 		        if (l_msg_data is not null) then
4513 			            x_msg_data  := x_msg_data || l_msg_data || '*';
4514 		        end if;
4515 		        x_msg_data := x_msg_data || '*' || l_result_rec.result_code;
4516 		        ROLLBACK TO ARI_Create_Cash_PVT;
4517 		        write_error_messages(x_msg_data, x_msg_count);
4518 		        RETURN;
4519 		END IF;
4520 	END IF;
4521 
4522   END IF;
4523 
4524 SAVEPOINT ARI_Create_Cash_PVT;
4525 
4526    IF p_cc_bill_to_site_id > 0 THEN
4527    ---------------------------------------------------------------------------------------------------------
4528     l_debug_info := 'CC billing site update required';
4529     ---------------------------------------------------------------------------------------------------------
4530 	   update_cc_bill_to_site(
4531 			p_cc_location_rec	=> l_cc_location_rec,
4532 			x_cc_bill_to_site_id	=> p_cc_bill_to_site_id ,
4533 			x_return_status		=> x_return_status,
4534 			x_msg_count		=> l_msg_count,
4535 			x_msg_data		=> l_msg_data);
4536 
4537 
4538 	  IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
4539 		p_status := FND_API.G_RET_STS_ERROR;
4540 		x_msg_count := x_msg_count + l_msg_count;
4541 		if (l_msg_data is not null) then
4542 			    x_msg_data  := x_msg_data || l_msg_data || '*';
4543 		end if;
4544 		x_msg_data := x_msg_data || '*' || l_result_rec.result_code;
4545 		ROLLBACK TO ARI_Create_Cash_PVT;
4546 		write_error_messages(x_msg_data, x_msg_count);
4547 		RETURN;
4548 	END IF;
4549 
4550    END IF;
4551 
4552   p_status := FND_API.G_RET_STS_SUCCESS;
4553 
4554   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
4555 	  fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,
4556                  'End-');
4557   end if;
4558 
4559 EXCEPTION
4560     WHEN OTHERS THEN
4561       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
4562       write_debug_and_log('- Customer Id: '||p_customer_id);
4563       write_debug_and_log('- Customer Site Id: '||p_site_use_id);
4564       write_debug_and_log('- Cash Receipt Id: '||p_cash_receipt_id);
4565       write_debug_and_log('- Return Status: '||p_status);
4566       write_debug_and_log('ERROR =>'|| SQLERRM);
4567 
4568       FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
4569       FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
4570       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4571       FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
4572       FND_MSG_PUB.ADD;
4573 
4574       p_status := FND_API.G_RET_STS_ERROR;
4575       write_error_messages(x_msg_data, x_msg_count);
4576 
4577 END pay_multiple_invoices;
4578 
4579 
4580 /*==============================================================
4581  | PROCEDURE process_payment
4582  |
4583  | DESCRIPTION
4584  |
4585  | PARAMETERS
4586  |
4587  | KNOWN ISSUES
4588  |
4589  | NOTES
4590  |   This procedure is the same as the on in the ar_receipt_api_pub.
4591  |   It was duplicated here in order to avoid exposing the api as a
4592  |   public api.
4593  |
4594  | MODIFICATION HISTORY
4595  | Date          Author       Description of Changes
4596  | 13-Jan-2003   krmenon      Created
4597  | 25-Feb-2004   vnb          Modified to add 'org_id' to rct_info
4598  |                            cursor,to be passed onto iPayment API
4599  | 07-Oct-2004   vnb          Bug 3335944 - One Time Credit Card Verification
4600  |
4601  +==============================================================*/
4602 PROCEDURE process_payment(
4603 	        p_cash_receipt_id     IN  NUMBER,
4604 	        p_payer_rec           IN  IBY_FNDCPT_COMMON_PUB.PayerContext_rec_type,
4605 	        P_payee_rec           IN  IBY_FNDCPT_TRXN_PUB.PayeeContext_rec_type,
4606                 p_called_from         IN  VARCHAR2,
4607                 p_response_error_code OUT NOCOPY VARCHAR2,
4608                 x_msg_count           OUT NOCOPY NUMBER,
4609                 x_msg_data            OUT NOCOPY VARCHAR2,
4610 	        x_return_status       OUT NOCOPY VARCHAR2
4611                 ) IS
4612 
4613   CURSOR rct_info_cur IS
4614      SELECT cr.receipt_number,
4615 	    cr.amount,
4616             cr.currency_code,
4617             rc.creation_status,
4618             cr.org_id,cr.payment_trxn_extension_id
4619      FROM   ar_cash_receipts cr,
4620             ar_receipt_methods rm,
4621 	    ar_receipt_classes rc
4622      WHERE  cr.cash_receipt_id = p_cash_receipt_id
4623        AND  cr.receipt_method_id = rm.receipt_method_id
4624        and  rm.receipt_class_id = rc.receipt_class_id;
4625 
4626 
4627   rct_info rct_info_cur%ROWTYPE;
4628 
4629   l_cr_rec ar_cash_receipts%ROWTYPE;
4630 
4631 
4632 
4633 l_auth_rec        IBY_FNDCPT_TRXN_PUB.AuthAttribs_rec_type;
4634 l_amount_rec      IBY_FNDCPT_TRXN_PUB.Amount_rec_type;
4635 x_auth_result     IBY_FNDCPT_TRXN_PUB.AuthResult_rec_type;
4636 x_response	  IBY_FNDCPT_COMMON_PUB.Result_rec_type;
4637 
4638 l_payment_trxn_extension_id number;
4639 
4640   l_action VARCHAR2(80);
4641 
4642   l_return_status VARCHAR2(1);
4643   l_msg_count NUMBER;
4644   l_msg_data  VARCHAR2(2000);
4645   l_procedure_name VARCHAR2(30);
4646   l_debug_info	   VARCHAR2(200);
4647 
4648 BEGIN
4649   --Assign default values
4650   l_return_status  := FND_API.G_RET_STS_SUCCESS;
4651   l_procedure_name := '.process_payment';
4652 
4653   arp_standard.debug('Entering credit card processing...'||p_cash_receipt_id);
4654   ---------------------------------------------------------------------------------
4655   l_debug_info := 'Entering credit card processing';
4656   ---------------------------------------------------------------------------------
4657   OPEN rct_info_cur;
4658   FETCH rct_info_cur INTO rct_info;
4659 
4660   IF rct_info_cur%FOUND THEN
4661         ---------------------------------------------------------------------------------
4662         l_debug_info := 'This is a credit card account - determining if capture is necessary';
4663         ---------------------------------------------------------------------------------
4664         write_debug_and_log('l_debug_info');
4665 
4666         -- determine whether to AUTHORIZE only or to
4667         -- CAPTURE and AUTHORIZE in one step.  This is
4668         -- dependent on the receipt creation status, i.e.,
4669         -- if the receipt is created as remitted or cleared, the
4670         -- funds need to be authorized and captured.  If the
4671         -- receipt is confirmed, the remittance process will
4672         -- handle the capture and at this time we'll only
4673         -- authorize the charges to the credit card.
4674 
4675         if rct_info.creation_status IN ('REMITTED', 'CLEARED') THEN
4676           l_action := 'AUTHANDCAPTURE';
4677         elsif rct_info.creation_status = 'CONFIRMED' THEN
4678           l_action := 'AUTHONLY';
4679         else
4680           arp_standard.debug('ERROR: Creation status is ' || rct_info.creation_status);
4681           FND_MESSAGE.set_name('AR', 'AR_PAY_PROCESS_INVALID_STATUS');
4682           FND_MSG_PUB.Add;
4683 
4684           x_return_status := FND_API.G_RET_STS_ERROR;  -- should never happen
4685           RETURN;
4686         end if;
4687         l_payment_trxn_extension_id:= rct_info.payment_trxn_extension_id;
4688         -- Step 1: (always performed):
4689         -- authorize credit card charge
4690 
4691         ---------------------------------------------------------------------------------
4692         l_debug_info := 'Authorize credit card charge: set auth record';
4693         ---------------------------------------------------------------------------------
4694 
4695      l_auth_rec.Memo := NULL;
4696      l_auth_rec.Order_Medium := NULL;
4697      l_auth_rec.ShipFrom_SiteUse_Id  := NULL;
4698      l_auth_rec.ShipFrom_PostalCode := NULL;
4699      l_auth_rec.ShipTo_SiteUse_Id  := NULL;
4700      l_auth_rec.ShipTo_PostalCode := NULL;
4701      l_auth_rec.RiskEval_Enable_Flag  := NULL;
4702 
4703      l_amount_rec.Value     := rct_info.amount;
4704      l_amount_rec.Currency_Code := rct_info.currency_code;
4705 
4706         -- call to iPayment API OraPmtReq to authorize funds
4707         write_debug_and_log('Calling Create_Authorization');
4708         write_debug_and_log('p_trxn_entity_id: ' || l_PAYMENT_TRXN_EXTENSION_ID);
4709         write_debug_and_log('p_payer_rec.payment_function:' || p_payer_rec.payment_function);
4710         write_debug_and_log('p_payer_rec.org_type: ' ||  p_payer_rec.org_type);
4711         write_debug_and_log('p_payer_rec.Cust_Account_Id: ' || p_payer_rec.Cust_Account_Id);
4712         write_debug_and_log('p_payer_rec.Account_Site_Id: ' ||p_payer_rec.Account_Site_Id );
4713 	write_debug_and_log('l_amount_rec.Value: ' || to_char(l_amount_rec.Value) );
4714         write_debug_and_log('l_amount_rec.Currency_Code: ' ||l_amount_rec.Currency_Code );
4715         write_debug_and_log('p_payee_rec.org_type: ' || p_payee_rec.org_type);
4716         write_debug_and_log('p_payee_rec.org_id : ' || p_payee_rec.org_id  );
4717 
4718         ---------------------------------------------------------------------------------
4719         l_debug_info := 'Call to iPayment API to authorize funds';
4720         ---------------------------------------------------------------------------------
4721 
4722 
4723         IBY_FNDCPT_TRXN_PUB.Create_Authorization(
4724 		    p_api_version	         => 1.0,
4725 		    p_init_msg_list		 => FND_API.G_TRUE,
4726 		    x_return_status		 => l_return_status,
4727 		    x_msg_count			 => l_msg_count,
4728 		    x_msg_data		         => l_msg_data,
4729 		    p_payer			 => p_payer_rec,
4730 		    p_payee			 => p_payee_rec,
4731 		    p_trxn_entity_id		 => l_PAYMENT_TRXN_EXTENSION_ID,
4732 		    p_auth_attribs		 => l_auth_rec,
4733 		    p_amount			 => l_amount_rec,
4734 		    x_auth_result		 => x_auth_result,
4735 		    x_response			 => x_response);
4736 
4737     	 arp_standard.debug('l_return_status: ' || l_return_status);
4738 
4739          x_msg_count           := l_msg_count;
4740          x_msg_data            := l_msg_data;
4741          p_response_error_code := x_response.Result_Code ;
4742 
4743          write_debug_and_log('-------------------------------------');
4744          write_debug_and_log('x_response.Result_Code: ' || x_response.Result_Code);
4745          write_debug_and_log('x_response.Result_Message: ' || x_response.Result_Message);
4746          write_debug_and_log('x_response.Result_Category: ' || x_response.Result_Category);
4747          write_debug_and_log('x_auth_result.Auth_Id : ' || x_auth_result.Auth_Id );
4748          write_debug_and_log('x_auth_result.Auth_Date: ' || TO_CHAR(x_auth_result.Auth_Date));
4749 	 write_debug_and_log('x_auth_result.Auth_Code: ' || x_auth_result.Auth_Code);
4750 	 write_debug_and_log('x_auth_result.AVS_Code: ' || x_auth_result.AVS_Code);
4751 	 write_debug_and_log('x_auth_result.Instr_SecCode_Check: ' || x_auth_result.Instr_SecCode_Check);
4752 	 write_debug_and_log('x_auth_result.PaymentSys_Code: ' || x_auth_result.PaymentSys_Code);
4753 	 write_debug_and_log('x_auth_result.PaymentSys_Msg: ' || x_auth_result.PaymentSys_Msg);
4754          write_debug_and_log('-------------------------------------');
4755 
4756         -- check if call was successful
4757         --Add message to message stack only it it is called from iReceivables
4758         --if not pass the message stack received from iPayment
4759 
4760         if (l_return_status <> FND_API.G_RET_STS_SUCCESS)
4761            AND (NVL(p_called_from,'NONE') = 'IREC')  then
4762 
4763           FND_MESSAGE.set_name('AR', 'AR_CC_AUTH_FAILED');
4764           FND_MSG_PUB.Add;
4765           x_return_status := l_return_status;
4766              --Bug 7673372 - When IBY API throws an error without contacting 3rd pmt system the error msg would
4767              --returned in x_response.Result_Message;
4768            x_msg_data := x_response.Result_Message;
4769           RETURN;
4770         elsif (l_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
4771           x_return_status := l_return_status;
4772           RETURN;
4773         end if;
4774 
4775         -- update cash receipt with authorization code
4776          ---------------------------------------------------------------------------------
4777         l_debug_info := 'update cash receipt with authorization code and payment server order id';
4778         ---------------------------------------------------------------------------------
4779 
4780         ARP_CASH_RECEIPTS_PKG.set_to_dummy(l_cr_rec);
4781         l_cr_rec.approval_code := x_auth_result.Auth_Code;
4782         ARP_CASH_RECEIPTS_PKG.update_p(l_cr_rec, p_cash_receipt_id);
4783 
4784           write_debug_and_log('CR rec updated with payment server auth code');
4785 
4786         -- see if capture is also required
4787 
4788         if (l_action = 'AUTHANDCAPTURE') then
4789 
4790           write_debug_and_log('starting capture...');
4791           ---------------------------------------------------------------------------------
4792           l_debug_info := 'Capture required: capture funds';
4793           ---------------------------------------------------------------------------------
4794           -- Step 2: (optional): capture funds
4795 
4796            ---------------------------------------------------------------------------------
4797           l_debug_info := 'Call iPayment API to capture funds';
4798           ---------------------------------------------------------------------------------
4799           IBY_FNDCPT_TRXN_PUB.Create_Settlement(
4800 		    p_api_version           => 1.0,
4801 		    p_init_msg_list         => FND_API.G_TRUE,
4802 		    x_return_status         => l_return_status,
4803 		    x_msg_count             => l_msg_count,
4804 		    x_msg_data              => l_msg_data,
4805 		    p_payer		    => p_payer_rec,
4806 		    p_trxn_entity_id	    => l_PAYMENT_TRXN_EXTENSION_ID,
4807 		    p_amount                => l_amount_rec,
4808 		    x_response              => x_response);
4809 
4810 
4811             write_debug_and_log('CAPTURE l_return_status: ' || l_return_status);
4812 
4813             x_msg_count           := l_msg_count;
4814             x_msg_data            := l_msg_data;
4815             p_response_error_code := x_response.Result_Code;
4816 
4817             arp_standard.debug('-------------------------------------');
4818             arp_standard.debug('x_response.Result_Code: ' ||x_response.Result_Code);
4819             arp_standard.debug('x_response.Result_Category: ' || x_response.Result_Category);
4820             arp_standard.debug('x_response.Result_Message: ' || x_response.Result_Message);
4821 
4822             arp_standard.debug('-------------------------------------');
4823 
4824            --Add message to message stack only it it is called from iReceivables
4825            --if not pass the message stack received from iPayment
4826 
4827            if (l_return_status <> FND_API.G_RET_STS_SUCCESS) AND (NVL(p_called_from,'NONE') = 'IREC')  then
4828               FND_MESSAGE.set_name('AR', 'AR_CC_CAPTURE_FAILED');
4829               FND_MSG_PUB.Add;
4830            end if;
4831            x_return_status := l_return_status;
4832              --Bug 7673372 - When IBY API throws an error without contacting 3rd pmt system the error msg would
4833              --returned in x_response.Result_Message;
4834            x_msg_data := x_response.Result_Message;
4835 
4836         END IF;  -- if capture required...
4837 
4838       ELSE
4839 
4840         write_debug_and_log('should never come here --> receipt method cursor has no rows');
4841         -- currently no processing required
4842 
4843     END IF;
4844 
4845 EXCEPTION
4846     WHEN OTHERS THEN
4847     	BEGIN
4848 	    x_return_status := FND_API.G_RET_STS_ERROR;
4849 
4850             write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
4851             write_debug_and_log('- Cash Receipt Id: '||p_cash_receipt_id);
4852             write_debug_and_log('- Return Status: '||x_return_status);
4853             write_debug_and_log(SQLERRM);
4854 
4855             FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
4856             FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
4857             FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
4858             FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
4859             FND_MSG_PUB.ADD;
4860         END;
4861 
4862 END process_payment;
4863 
4864 
4865 FUNCTION validate_payment_setup (p_customer_id IN NUMBER , p_customer_site_id IN NUMBER , p_currency_code IN VARCHAR2) RETURN NUMBER
4866 IS
4867 
4868   l_ccmethodcount NUMBER;
4869   l_bamethodcount NUMBER; /* J Rautiainen ACH Implementation */
4870   l_creation_status ar_receipt_classes.creation_status%TYPE;
4871   l_procedure_name VARCHAR2(30);
4872 BEGIN
4873 
4874   l_procedure_name  := '.validate_payment_setup';
4875 
4876   -- check that function security is allowing access to payment button
4877 
4878   IF NOT fnd_function.test('ARW_PAY_INVOICE') THEN
4879     RETURN 0;
4880   END IF;
4881 
4882   -- verify that payment method is set up
4883   l_ccmethodcount  := is_credit_card_payment_enabled(p_customer_id , p_customer_site_id , p_currency_code) ;
4884 
4885   -- Bug 3338276
4886   -- If one-time payment is enabled, bank account payment is not enabled;
4887   -- Hence, the check for valid bank account payment methods can be defaulted to 0.
4888   -- Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.save_payment_instrument_info
4889   IF NOT ARI_UTILITIES.save_payment_instrument_info(p_customer_id , p_customer_site_id) THEN
4890     l_bamethodcount := 0;
4891   ELSE
4892     l_bamethodcount := is_bank_acc_payment_enabled(p_customer_id , p_customer_site_id , p_currency_code);
4893   END IF;
4894 
4895    IF   l_ccmethodcount  = 0
4896    AND l_bamethodcount = 0  /* J Rautiainen ACH Implementation */
4897    THEN
4898     RETURN 0;
4899   END IF;
4900 
4901   RETURN 1;
4902 
4903 END validate_payment_setup;
4904 
4905 /*============================================================
4906   | PUBLIC procedure create_transaction_list_record
4907   |
4908   | DESCRIPTION
4909   |   Creates a record in the transaction List to be paid by the customer
4910   |   based on the selected list .
4911   |
4912   | PSEUDO CODE/LOGIC
4913   |
4914   | PARAMETERS
4915   |   p_payment_schedule_id   IN    NUMBER
4916   |   p_customer_id	      IN    NUMBER
4917   |   p_customer_site_id      IN    NUMBER
4918   |
4919   | KNOWN ISSUES
4920   |
4921   |
4922   |
4923   | NOTES
4924   |
4925   |
4926   |
4927   | MODIFICATION HISTORY
4928   | Date          Author       Description of Changes
4929   | 27-JUN-2003   yreddy       Created
4930   | 31-DEC-2004   vnb          Bug 4071551 - Modified for avoiding redundant code
4931   | 20-Jan-2005   vnb          Bug 4117211 - Original discount amount column added for ease of resetting payment amounts
4932   | 26-May-05     rsinthre     Bug # 4392371 - OIR needs to support cross customer payment
4933   | 08-Jul-2005	  rsinthre     Bug 4437225 - Disputed amount against invoice not displayed during payment
4934   +============================================================*/
4935 PROCEDURE create_transaction_list_record( p_payment_schedule_id   IN NUMBER,
4936 					  p_customer_id           IN NUMBER,
4937 					  p_customer_site_id	  IN NUMBER
4938                                   ) IS
4939 
4940   l_query_period             NUMBER(15);
4941   l_query_date               DATE;
4942   l_total_service_charge     NUMBER;
4943   l_discount_amount          NUMBER;
4944   l_rem_amt_rcpt             NUMBER;
4945   l_rem_amt_inv              NUMBER;
4946   l_amount_due_remaining     NUMBER;
4947   l_trx_class                VARCHAR2(20);
4948   l_cash_receipt_id          NUMBER;
4949   l_grace_days_flag          VARCHAR2(2);
4950 
4951   l_pay_for_cust_id	     NUMBER(15);
4952   l_paying_cust_id	     NUMBER(15);
4953   l_pay_for_cust_site_id     NUMBER(15);
4954   l_paying_cust_site_id      NUMBER(15);
4955   l_dispute_amount	     NUMBER := 0;
4956   l_customer_trx_id	     NUMBER(15,0);
4957 
4958   l_procedure_name           VARCHAR2(50);
4959   l_debug_info	 	     VARCHAR2(200);
4960 
4961 BEGIN
4962   --Assign default values
4963   l_query_period         := -12;
4964   l_total_service_charge := 0;
4965   l_discount_amount      := 0;
4966   l_rem_amt_rcpt         := 0;
4967   l_rem_amt_inv          := 0;
4968   l_amount_due_remaining := 0;
4969 
4970   l_procedure_name       := '.create_transaction_list_record';
4971 
4972   SAVEPOINT create_trx_list_record_sp;
4973 
4974   select class, amount_due_remaining, cash_receipt_id, ps.CUSTOMER_ID, ct.PAYING_CUSTOMER_ID, ps.CUSTOMER_SITE_USE_ID,ct.PAYING_SITE_USE_ID, ps.customer_trx_id,
4975     (decode( nvl(AMOUNT_DUE_ORIGINAL,0),0,1,(AMOUNT_DUE_ORIGINAL/abs(AMOUNT_DUE_ORIGINAL)) ) *abs(nvl(amount_in_dispute,0)) )
4976   into l_trx_class, l_amount_due_remaining, l_cash_receipt_id, l_pay_for_cust_id, l_paying_cust_id, l_pay_for_cust_site_id, l_paying_cust_site_id, l_customer_trx_id, l_dispute_amount
4977   from ar_payment_schedules ps, ra_customer_trx_all ct
4978   where ps.CUSTOMER_TRX_ID = ct.CUSTOMER_TRX_ID(+)
4979   and ps.payment_schedule_id = p_payment_schedule_id;
4980 
4981    --Bug 4479224
4982    l_paying_cust_id := p_customer_id;
4983    l_paying_cust_site_id := p_customer_site_id;
4984 
4985   ----------------------------------------------------------------------------------------
4986   l_debug_info := 'If the transaction is a Payment, then set the Remaining Amount';
4987   -----------------------------------------------------------------------------------------
4988   IF (PG_DEBUG = 'Y') THEN
4989         arp_standard.debug(l_debug_info);
4990   END IF;
4991   -- Bug 4000279 - Modified to check for 'UNAPP' status only
4992   IF (l_trx_class = 'PMT') THEN
4993 
4994 	select -sum(app.amount_applied)
4995         into  l_amount_due_remaining
4996  	from ar_receivable_applications app
4997 	where nvl( app.confirmed_flag, 'Y' ) = 'Y'
4998         and app.status = 'UNAPP'
4999         and app.cash_receipt_id = l_cash_receipt_id;
5000    ----------------------------------------------------------------------------------------
5001    l_debug_info := 'If the transaction is a debit, then calculate discount';
5002    -----------------------------------------------------------------------------------------
5003    IF (PG_DEBUG = 'Y') THEN
5004         arp_standard.debug(l_debug_info);
5005    END IF;
5006    ELSIF (l_trx_class = 'INV' OR l_trx_class = 'DEP' OR l_trx_class = 'DM' OR l_trx_class = 'CB') THEN
5007 	  --Bug 6819964 - If AR API errors out then payments are failing as l_discount_amount is not set to any value
5008 	  begin
5009         	--l_grace_days_flag := is_grace_days_enabled_wrapper();
5010         	l_grace_days_flag := ARI_UTILITIES.is_discount_grace_days_enabled(p_customer_id,p_customer_site_id);
5011         	arp_discounts_api.get_discount(p_ps_id	            => p_payment_schedule_id,
5012 		                       p_apply_date	    => trunc(sysdate),
5013                             	       p_in_applied_amount  => (l_amount_due_remaining - l_dispute_amount),
5014 		                       p_grace_days_flag    => l_grace_days_flag,
5015 		                       p_out_discount       => l_discount_amount,
5016 		                       p_out_rem_amt_rcpt   => l_rem_amt_rcpt,
5017 		                       p_out_rem_amt_inv    => l_rem_amt_inv,
5018 				       p_called_from        => 'OIR' );
5019 	  exception
5020 		when others then
5021 			l_discount_amount := 0;
5022 			write_debug_and_log('Unexpected Exception while calculating discount');
5023 			write_debug_and_log('Payment Schedule Id: '||p_payment_schedule_id);
5024 	  end;
5025    END IF;
5026 
5027     --Bug 4117211 - Original discount amount column added for ease of resetting payment amounts
5028     ----------------------------------------------------------------------------------------
5029     l_debug_info := 'Populate the Payment GT with the transaction';
5030     -----------------------------------------------------------------------------------------
5031     IF (PG_DEBUG = 'Y') THEN
5032         arp_standard.debug(l_debug_info);
5033     END IF;
5034 
5035     INSERT INTO AR_IREC_PAYMENT_LIST_GT
5036       ( CUSTOMER_ID,
5037         CUSTOMER_SITE_USE_ID,
5038         ACCOUNT_NUMBER,
5039         CUSTOMER_TRX_ID,
5040         TRX_NUMBER,
5041         PAYMENT_SCHEDULE_ID,
5042         TRX_DATE,
5043         DUE_DATE,
5044         STATUS,
5045         TRX_CLASS,
5046         PO_NUMBER,
5047         SO_NUMBER,
5048         CURRENCY_CODE,
5049         AMOUNT_DUE_ORIGINAL,
5050         AMOUNT_DUE_REMAINING,
5051         DISCOUNT_AMOUNT,
5052         SERVICE_CHARGE,
5053         PAYMENT_AMT,
5054         PAYMENT_TERMS,
5055         NUMBER_OF_INSTALLMENTS,
5056         TERMS_SEQUENCE_NUMBER,
5057         LINE_AMOUNT,
5058         TAX_AMOUNT,
5059         FREIGHT_AMOUNT,
5060         FINANCE_CHARGES,
5061         RECEIPT_DATE,
5062         PRINTING_OPTION,
5063 	INTERFACE_HEADER_CONTEXT,
5064         INTERFACE_HEADER_ATTRIBUTE1,
5065         INTERFACE_HEADER_ATTRIBUTE2,
5066         INTERFACE_HEADER_ATTRIBUTE3,
5067         INTERFACE_HEADER_ATTRIBUTE4,
5068         INTERFACE_HEADER_ATTRIBUTE5,
5069         INTERFACE_HEADER_ATTRIBUTE6,
5070         INTERFACE_HEADER_ATTRIBUTE7,
5071         INTERFACE_HEADER_ATTRIBUTE8,
5072         INTERFACE_HEADER_ATTRIBUTE9,
5073         INTERFACE_HEADER_ATTRIBUTE10,
5074         INTERFACE_HEADER_ATTRIBUTE11,
5075         INTERFACE_HEADER_ATTRIBUTE12,
5076         INTERFACE_HEADER_ATTRIBUTE13,
5077         INTERFACE_HEADER_ATTRIBUTE14,
5078         INTERFACE_HEADER_ATTRIBUTE15,
5079         ATTRIBUTE_CATEGORY,
5080         ATTRIBUTE1,
5081         ATTRIBUTE2,
5082         ATTRIBUTE3,
5083         ATTRIBUTE4,
5084         ATTRIBUTE5,
5085         ATTRIBUTE6,
5086         ATTRIBUTE7,
5087         ATTRIBUTE8,
5088         ATTRIBUTE9,
5089         ATTRIBUTE10,
5090         ATTRIBUTE11,
5091         ATTRIBUTE12,
5092         ATTRIBUTE13,
5093         ATTRIBUTE14,
5094         ATTRIBUTE15,
5095         CASH_RECEIPT_ID,
5096 	ORIGINAL_DISCOUNT_AMT,
5097     ORG_ID,
5098 	PAY_FOR_CUSTOMER_ID,
5099 	PAY_FOR_CUSTOMER_SITE_ID,
5100 	DISPUTE_AMT
5101       )
5102        SELECT l_paying_cust_id,
5103          decode(l_paying_cust_site_id, null, -1,to_number(''), -1, l_paying_cust_site_id),
5104          acct.ACCOUNT_NUMBER,
5105          ps.CUSTOMER_TRX_ID,
5106          ps.TRX_NUMBER,
5107          ps.PAYMENT_SCHEDULE_ID,
5108          ps.TRX_DATE,
5109          ps.DUE_DATE,
5110          ps.STATUS,
5111          ps.class,
5112          ct.PURCHASE_ORDER AS PO_NUMBER,
5113          NULL AS SO_NUMBER,
5114 	 ps.INVOICE_CURRENCY_CODE,
5115 	 ps.AMOUNT_DUE_ORIGINAL,
5116          l_amount_due_remaining,
5117 	 l_discount_amount,
5118 	 0,
5119 	 DECODE(ps.class, 'PMT', l_amount_due_remaining, 'CM', l_amount_due_remaining,
5120 			ARI_UTILITIES.curr_round_amt(l_amount_due_remaining-l_discount_amount -l_dispute_amount,ps.INVOICE_CURRENCY_CODE)),
5121          trm.name term_desc,
5122 	 ARPT_SQL_FUNC_UTIL.Get_Number_Of_Due_Dates(ps.term_id) number_of_installments,
5123          ps.terms_sequence_number,
5124          ps.amount_line_items_original line_amount,
5125          ps.tax_original tax_amount,
5126          ps.freight_original freight_amount,
5127          ps.receivables_charges_charged finance_charge,
5128          TRUNC(SYSDATE) receipt_date,
5129          ct.printing_option,
5130 	 ct.INTERFACE_HEADER_CONTEXT,
5131          ct.INTERFACE_HEADER_ATTRIBUTE1,
5132          ct.INTERFACE_HEADER_ATTRIBUTE2,
5133          ct.INTERFACE_HEADER_ATTRIBUTE3,
5134          ct.INTERFACE_HEADER_ATTRIBUTE4,
5135          ct.INTERFACE_HEADER_ATTRIBUTE5,
5136          ct.INTERFACE_HEADER_ATTRIBUTE6,
5137          ct.INTERFACE_HEADER_ATTRIBUTE7,
5138          ct.INTERFACE_HEADER_ATTRIBUTE8,
5139          ct.INTERFACE_HEADER_ATTRIBUTE9,
5140          ct.INTERFACE_HEADER_ATTRIBUTE10,
5141          ct.INTERFACE_HEADER_ATTRIBUTE11,
5142          ct.INTERFACE_HEADER_ATTRIBUTE12,
5143          ct.INTERFACE_HEADER_ATTRIBUTE13,
5144          ct.INTERFACE_HEADER_ATTRIBUTE14,
5145          ct.INTERFACE_HEADER_ATTRIBUTE15,
5146          ct.ATTRIBUTE_CATEGORY,
5147          ct.ATTRIBUTE1,
5148          ct.ATTRIBUTE2,
5149          ct.ATTRIBUTE3,
5150          ct.ATTRIBUTE4,
5151          ct.ATTRIBUTE5,
5152          ct.ATTRIBUTE6,
5153          ct.ATTRIBUTE7,
5154          ct.ATTRIBUTE8,
5155          ct.ATTRIBUTE9,
5156          ct.ATTRIBUTE10,
5157          ct.ATTRIBUTE11,
5158          ct.ATTRIBUTE12,
5159          ct.ATTRIBUTE13,
5160          ct.ATTRIBUTE14,
5161          ct.ATTRIBUTE15,
5162          ps.cash_receipt_id,
5163 	 l_discount_amount,
5164 	 ps.org_id,
5165 	 l_pay_for_cust_id,
5166 	 --Bug 4062938 - Handling of transactions with no site id
5167 	 decode(ps.customer_site_use_id, null, -1,ps.customer_site_use_id) as CUSTOMER_SITE_USE_ID,
5168 	 (decode( nvl(ps.AMOUNT_DUE_ORIGINAL,0),0,1,(ps.AMOUNT_DUE_ORIGINAL/abs(ps.AMOUNT_DUE_ORIGINAL)) ) *abs(nvl(ps.amount_in_dispute,0)) )
5169       FROM AR_PAYMENT_SCHEDULES ps,
5170            RA_CUSTOMER_TRX_ALL ct,
5171            HZ_CUST_ACCOUNTS acct,
5172            RA_TERMS trm
5173       WHERE ps.payment_schedule_id = p_payment_schedule_id
5174       AND   ps.CLASS IN ('INV', 'DM', 'GUAR', 'CB', 'DEP', 'CM', 'PMT' )  -- CCA - hikumar
5175       AND   ps.customer_trx_id = ct.customer_trx_id(+)
5176       AND   acct.cust_account_id = ps.customer_id
5177       AND   ps.term_id = trm.term_id(+);
5178 
5179    COMMIT;
5180 
5181 EXCEPTION
5182      WHEN OTHERS THEN
5183          IF (PG_DEBUG = 'Y') THEN
5184              arp_standard.debug('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
5185              arp_standard.debug('- Payment Schedule Id: '||p_payment_schedule_id);
5186              arp_standard.debug('ERROR =>'|| SQLERRM);
5187          END IF;
5188 
5189 	 ROLLBACK to create_trx_list_record_sp;
5190 
5191          FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
5192          FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
5193          FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5194          FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
5195          FND_MSG_PUB.ADD;
5196 
5197 END create_transaction_list_record;
5198 
5199 /*========================================================================
5200  | PUBLIC procedure is_credit_card_payment_enabled
5201  |
5202  | DESCRIPTION
5203  |      Checks if the credit card payment method has been setup
5204  |      ----------------------------------------
5205  |
5206  | PSEUDO CODE/LOGIC
5207  |
5208  | PARAMETERS
5209  |
5210  | RETURNS
5211  |      Number 1 or 0 corresponing to true and false for the credit card
5212  |      payment has been setup or not.
5213  |
5214  | MODIFICATION HISTORY
5215  | Date          Author       Description of Changes
5216  | 10-Mar-2004   hikumar       Created
5217  ========================================================================*/
5218 
5219 FUNCTION is_credit_card_payment_enabled(p_customer_id IN NUMBER , p_customer_site_id IN NUMBER , p_currency_code IN VARCHAR2)
5220 RETURN NUMBER IS
5221 system_cc_payment_method	NUMBER ;
5222 customer_cc_payment_method      NUMBER ;
5223 profile_cc_payment_method VARCHAR2(200);
5224 
5225 CURSOR cc_profile_pmt_method_info_cur IS
5226   SELECT arm.receipt_method_id receipt_method_id,
5227     arc.creation_status receipt_creation_status
5228   FROM ar_receipt_methods arm,
5229     ar_receipt_method_accounts arma,
5230     ce_bank_acct_uses_ou_v aba,
5231     ce_bank_accounts       cba,
5232     ar_receipt_classes arc
5233   WHERE arm.payment_channel_code = 'CREDIT_CARD'
5234     AND arm.receipt_method_id = NVL( to_number(fnd_profile.VALUE('OIR_CC_PMT_METHOD')), arm.receipt_method_id)
5235     AND arm.receipt_method_id = arma.receipt_method_id
5236     AND arm.receipt_class_id = arc.receipt_class_id
5237     AND arma.remit_bank_acct_use_id = aba.bank_acct_use_id
5238     AND aba.bank_account_id = cba.bank_account_id
5239     AND (cba.currency_code = p_currency_code OR cba.receipt_multi_currency_flag = 'Y')
5240     AND TRUNC(nvl(aba.end_date,sysdate)) >= TRUNC(sysdate)
5241     AND TRUNC(sysdate) BETWEEN TRUNC(nvl(arm.start_date,   sysdate)) AND TRUNC(nvl(arm.end_date,   sysdate))
5242     AND TRUNC(sysdate) BETWEEN TRUNC(arma.start_date) AND TRUNC(nvl(arma.end_date,   sysdate));
5243 
5244 
5245 
5246  cc_profile_pmt_method_info cc_profile_pmt_method_info_cur%ROWTYPE;
5247 
5248  l_procedure_name  VARCHAR2(30);
5249  l_debug_info  VARCHAR2(300);
5250 
5251 BEGIN
5252 
5253 l_procedure_name := 'is_credit_card_payment_enabled';
5254 
5255    --------------------------------------------------------------------
5256    l_debug_info := 'Checking if valid CC payment method is set in the profile OIR_CC_PMT_METHOD';
5257    --------------------------------------------------------------------
5258      IF (PG_DEBUG = 'Y') THEN
5259         arp_standard.debug(l_debug_info);
5260      END IF;
5261 
5262   profile_cc_payment_method := FND_PROFILE.value('OIR_CC_PMT_METHOD');
5263 
5264   IF (profile_cc_payment_method = 'DISABLED') THEN   /* Credit Card Payment is Disabled */
5265     RETURN 0;
5266   ELSIF (profile_cc_payment_method IS NOT NULL) THEN /* A Credit Card Payment Method has been mentioned */
5267     OPEN  cc_profile_pmt_method_info_cur;
5268     FETCH cc_profile_pmt_method_info_cur INTO cc_profile_pmt_method_info;
5269     /* If CC Payment Method set is NULL or DISABLED or an invalid payment method, it returns NO rows */
5270     IF cc_profile_pmt_method_info_cur%FOUND THEN
5271        l_debug_info := 'Payment Method Set in the profile OIR_CC_PMT_METHOD is Valid. Val=' ||  fnd_profile.VALUE('OIR_CC_PMT_METHOD');
5272         if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
5273          fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
5274         end if;
5275       RETURN 1;
5276      ELSE
5277       l_debug_info := 'Invalid Payment Method is Set in the profile OIR_CC_PMT_METHOD. Value in profile=' ||  fnd_profile.VALUE('OIR_CC_PMT_METHOD');
5278        if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
5279           fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
5280        end if;
5281       RETURN 0;
5282     END IF;
5283    CLOSE cc_profile_pmt_method_info_cur;
5284 
5285   END IF;
5286 
5287   l_debug_info := 'No value is set in the profile OIR_CC_PMT_METHOD. Checking at customer site, acct and system options level.';
5288 
5289      if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
5290         fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
5291      end if;
5292 
5293  /* Default behavior, as no Credit Card Payment method is mentioned in the OIR_CC_PMT_METHOD profile */
5294 
5295  -- verify that Credit Card payment method is set up in AR_SYSTEM_PARAMETERS
5296   -- Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.save_payment_instrument_info
5297   SELECT  /*+ leading(rc) */  count(irec_cc_receipt_method_id)
5298   INTO system_cc_payment_method
5299   FROM   ar_system_parameters sp,
5300          ar_receipt_methods rm,
5301          ar_receipt_method_accounts rma,
5302          ce_bank_accounts cba,
5303          ce_bank_acct_uses_ou_v ba,
5304          ar_receipt_classes rc
5305   WHERE  sp.irec_cc_receipt_method_id = rm.receipt_method_id
5306     AND  rma.receipt_method_id = rm.receipt_method_id
5307     AND  rma.remit_bank_acct_use_id = ba.bank_acct_use_id
5308     AND  ba.bank_account_id = cba.bank_account_id
5309     AND  ( cba.currency_code = p_currency_code
5310 	    OR
5311 	   cba.receipt_multi_currency_flag = 'Y' )
5312     AND  sysdate < nvl(ba.end_date, SYSDATE+1)
5313     AND  sysdate between rma.start_date and nvl(rma.end_date, SYSDATE)
5314     AND  sysdate between rm.start_date and NVL(rm.end_date, SYSDATE)
5315      AND (
5316            save_payment_inst_info_wrapper(p_customer_id,p_customer_site_id) = 'true'
5317           OR
5318              -- If the one time payment is true , then ensure that the receipt
5319               -- class is set for one step remittance.
5320               rc.creation_status IN ('REMITTED','CLEARED'))
5321               and rc.receipt_class_id = rm.receipt_class_id;
5322 
5323  -- verify that Credit Card payment method is set up at Customer Account Level or Site Level
5324 
5325   SELECT count ( arm.receipt_method_id )
5326   INTO customer_cc_payment_method
5327   FROM    ar_receipt_methods         arm,
5328           ra_cust_receipt_methods    rcrm,
5329           ar_receipt_method_accounts arma,
5330           ce_bank_acct_uses_ou_v          aba,
5331           ce_bank_accounts           cba,
5332           ar_receipt_classes         arc
5333   WHERE   arm.receipt_method_id = rcrm.receipt_method_id
5334      AND       arm.receipt_method_id = arma.receipt_method_id
5335      AND       arm.receipt_class_id  = arc.receipt_class_id
5336      AND       rcrm.customer_id      = p_customer_id
5337      AND       arma.remit_bank_acct_use_id = aba.bank_acct_use_id
5338      AND       aba.bank_account_id = cba.bank_account_id
5339      AND     ( NVL(rcrm.site_use_id,p_customer_site_id)  = p_customer_site_id
5340                OR
5341                (p_customer_site_id is null and rcrm.site_use_id is null)
5342               )
5343      AND   (
5344                  cba.currency_code    =  p_currency_code
5345                  OR
5346                  cba.receipt_multi_currency_flag = 'Y'
5347               )
5348 -- Bug#6109909
5349 --     AND  arm.payment_type_code = 'CREDIT_CARD'
5350      AND  arm.payment_channel_code = 'CREDIT_CARD'
5351      AND  arc.creation_method_code = 'AUTOMATIC'
5352      -- AND       aba.set_of_books_id = arp_trx_global.system_info.system_parameters.set_of_books_id
5353      AND sysdate < NVL ( aba.end_date , sysdate+1)
5354      AND sysdate between arm.start_date AND NVL(arm.end_date, sysdate)
5355      AND sysdate between arma.start_date AND NVL(arma.end_date, sysdate)
5356      AND (
5357           ( save_payment_inst_info_wrapper(p_customer_id,p_customer_site_id) = 'true' )
5358           OR
5359           (   -- If the one time payment is true , then ensure that the receipt
5360               -- class is set for one step remittance.
5361             arc.creation_status IN ('REMITTED','CLEARED')
5362           )
5363          )
5364       ;
5365 
5366   IF( (customer_cc_payment_method = 0 ) AND  (system_cc_payment_method = 0))
5367   THEN
5368     RETURN 0 ;
5369   ELSE
5370     RETURN 1 ;
5371   END IF;
5372 
5373 EXCEPTION
5374 WHEN OTHERS THEN
5375         l_debug_info := 'Unknown exception. Value in profile OIR_CC_PMT_METHOD=' ||  fnd_profile.VALUE('OIR_CC_PMT_METHOD');
5376         write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
5377        	write_debug_and_log('ERROR =>'|| SQLERRM);
5378         write_debug_and_log('-DEBUG_INFO-' || l_debug_info);
5379         RETURN 0;
5380 
5381 END is_credit_card_payment_enabled ;
5382 
5383 
5384 
5385 
5386 /*========================================================================
5387  | PUBLIC procedure is_bank_acc_payment_enabled
5388  |
5389  | DESCRIPTION
5390  |      Checks if the Bank Account payment method has been setup
5391  |      ----------------------------------------
5392  |
5393  | PSEUDO CODE/LOGIC
5394  |
5395  | PARAMETERS
5396  |
5397  | RETURNS
5398  |      Number 1 or 0 corresponing to true and false for the credit card
5399  |      payment has been setup or not.
5400  |
5401  | MODIFICATION HISTORY
5402  | Date          Author       Description of Changes
5403  | 10-Mar-2004   hikumar       Created
5404  ========================================================================*/
5405 
5406 FUNCTION is_bank_acc_payment_enabled(p_customer_id IN NUMBER , p_customer_site_id IN NUMBER , p_currency_code IN VARCHAR2)
5407 RETURN NUMBER IS
5408 system_bank_payment_method  	NUMBER ;
5409 customer_bank_payment_method    NUMBER ;
5410 profile_ba_payment_method VARCHAR2(200);
5411 
5412 CURSOR ba_profile_pmt_method_info_cur IS
5413   SELECT arm.receipt_method_id receipt_method_id,
5414     arc.creation_status receipt_creation_status
5415   FROM ar_receipt_methods arm,
5416     ar_receipt_method_accounts arma,
5417     ce_bank_acct_uses_ou_v aba,
5418     ce_bank_accounts       cba,
5419     ar_receipt_classes arc
5420   WHERE NVL(arm.payment_channel_code,'NONE') <> 'CREDIT_CARD'
5421     AND arm.receipt_method_id = NVL( to_number(fnd_profile.VALUE('OIR_BA_PMT_METHOD')), arm.receipt_method_id)
5422     AND arm.receipt_method_id = arma.receipt_method_id
5423     AND arm.receipt_class_id = arc.receipt_class_id
5424     AND arma.remit_bank_acct_use_id = aba.bank_acct_use_id
5425     AND aba.bank_account_id = cba.bank_account_id
5426     AND (cba.currency_code = p_currency_code OR cba.receipt_multi_currency_flag = 'Y')
5427     AND TRUNC(nvl(aba.end_date,sysdate)) >= TRUNC(sysdate)
5428     AND TRUNC(sysdate) BETWEEN TRUNC(nvl(arm.start_date,   sysdate)) AND TRUNC(nvl(arm.end_date,   sysdate))
5429     AND TRUNC(sysdate) BETWEEN TRUNC(arma.start_date) AND TRUNC(nvl(arma.end_date,   sysdate));
5430 
5431  ba_profile_pmt_method_info ba_profile_pmt_method_info_cur%ROWTYPE;
5432 
5433  l_procedure_name  VARCHAR2(30);
5434  l_debug_info  VARCHAR2(300);
5435 
5436 BEGIN
5437 
5438 l_procedure_name := 'is_bank_acc_payment_enabled';
5439 
5440    --------------------------------------------------------------------
5441    l_debug_info := 'Checking if valid Bank Account payment method is set in the profile OIR_BA_PMT_METHOD';
5442    --------------------------------------------------------------------
5443      IF (PG_DEBUG = 'Y') THEN
5444         arp_standard.debug(l_debug_info);
5445      END IF;
5446 
5447   profile_ba_payment_method := FND_PROFILE.value('OIR_BA_PMT_METHOD');
5448 
5449   IF (profile_ba_payment_method = 'DISABLED') THEN   /* Bank Account Payment is Disabled */
5450     RETURN 0;
5451   ELSIF (profile_ba_payment_method IS NOT NULL) THEN /* A Bank Account Payment Method has been mentioned */
5452     OPEN  ba_profile_pmt_method_info_cur;
5453     FETCH ba_profile_pmt_method_info_cur INTO ba_profile_pmt_method_info;
5454     /* If Bank Account Payment Method set is NULL or DISABLED or an invalid payment method, it returns NO rows */
5455     IF ba_profile_pmt_method_info_cur%FOUND THEN
5456        l_debug_info := 'Payment Method Set in the profile OIR_BA_PMT_METHOD is Valid. Val=' ||  fnd_profile.VALUE('OIR_BA_PMT_METHOD');
5457         if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
5458          fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
5459         end if;
5460       RETURN 1;
5461      ELSE
5462       l_debug_info := 'Invalid Payment Method is Set in the profile OIR_BA_PMT_METHOD. Value in profile=' ||  fnd_profile.VALUE('OIR_BA_PMT_METHOD');
5463        if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
5464           fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
5465        end if;
5466       RETURN 0;
5467     END IF;
5468    CLOSE ba_profile_pmt_method_info_cur;
5469 
5470   END IF;
5471 
5472   l_debug_info := 'No value is set in the profile OIR_BA_PMT_METHOD. Checking at customer site, acct and system options level.';
5473 
5474      if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
5475         fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, l_debug_info);
5476      end if;
5477 
5478  /* Default behavior, as no Bank Account Payment method is mentioned in the OIR_BA_PMT_METHOD profile */
5479 
5480  -- verify that Bank Account payment method is set up in AR_SYSTEM_PARAMETERS
5481 
5482   SELECT count(irec_ba_receipt_method_id) /* J Rautiainen ACH Implementation */
5483   INTO system_bank_payment_method
5484   FROM   ar_system_parameters sp,
5485          ar_receipt_methods rm,
5486          ar_receipt_method_accounts rma,
5487          ce_bank_acct_uses_ou_v ba,
5488          ce_bank_accounts cba
5489   WHERE  sp.irec_ba_receipt_method_id = rm.receipt_method_id
5490     AND  rma.receipt_method_id = rm.receipt_method_id
5491     AND  rma.remit_bank_acct_use_id = ba.bank_acct_use_id
5492     AND  ba.bank_account_id = cba.bank_account_id
5493     AND  ( cba.currency_code = p_currency_code
5494 	    OR cba.receipt_multi_currency_flag = 'Y')
5495     AND  sysdate < nvl(ba.end_date, SYSDATE+1)
5496     AND  sysdate between rma.start_date and nvl(rma.end_date, SYSDATE)
5497     AND  sysdate between rm.start_date and NVL(rm.end_date, SYSDATE);
5498 
5499  -- verify that Bank Account payment method is set up in AR_SYSTEM_PARAMETERS
5500 
5501   SELECT count ( arm.receipt_method_id )
5502   INTO customer_bank_payment_method
5503   FROM    ar_receipt_methods         arm,
5504           ra_cust_receipt_methods    rcrm,
5505           ar_receipt_method_accounts arma,
5506           ce_bank_acct_uses_ou_v          aba,
5507           ce_bank_accounts           cba,
5508           ar_receipt_classes         arc
5509   WHERE   arm.receipt_method_id = rcrm.receipt_method_id
5510     AND       arm.receipt_method_id = arma.receipt_method_id
5511     AND       arm.receipt_class_id  = arc.receipt_class_id
5512     AND       rcrm.customer_id      = p_customer_id
5513     AND       arma.remit_bank_acct_use_id  = aba.bank_acct_use_id
5514     AND       aba.bank_account_id = cba.bank_account_id
5515     AND     ( NVL(rcrm.site_use_id,p_customer_site_id)  = p_customer_site_id
5516               OR
5517              (p_customer_site_id is null and rcrm.site_use_id is null)
5518             )
5519     AND   (
5520                  cba.currency_code    =  p_currency_code
5521                  OR
5522                  cba.receipt_multi_currency_flag = 'Y'
5523             )
5524    AND   (   arc.remit_flag = 'Y'
5525              and arc.confirm_flag = 'N'
5526 	  )
5527    AND (
5528 	  arc.creation_method_code = 'MANUAL'
5529 	  or
5530    --Bug#6109909
5531           ( arm.payment_channel_code = 'BANK_ACCT_XFER'
5532 	    and arc.creation_method_code = 'AUTOMATIC' )
5533 	)
5534    -- AND       aba.set_of_books_id = arp_trx_global.system_info.system_parameters.set_of_books_id
5535    AND sysdate < NVL ( aba.end_date , sysdate+1)
5536    AND sysdate between arm.start_date AND NVL(arm.end_date, sysdate)
5537    AND sysdate between arma.start_date AND NVL(arma.end_date, sysdate) ;
5538 
5539   IF( (customer_bank_payment_method = 0) AND  (system_bank_payment_method = 0))
5540   THEN
5541     RETURN 0 ;
5542   ELSE
5543     RETURN 1 ;
5544   END IF;
5545 
5546 EXCEPTION
5547 WHEN OTHERS THEN
5548         l_debug_info := 'Unknown exception. Value in profile OIR_BA_PMT_METHOD=' ||  fnd_profile.VALUE('OIR_BA_PMT_METHOD');
5549         write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
5550        	write_debug_and_log('ERROR =>'|| SQLERRM);
5551         write_debug_and_log('-DEBUG_INFO-' || l_debug_info);
5552         RETURN 0;
5553 
5554 END is_bank_acc_payment_enabled ;
5555 
5556 /*============================================================
5557   | PUBLIC function save_payment_inst_info_wrapper
5558   |
5559   | DESCRIPTION
5560   |   This is a wrapper to return a VARCHAR2 instead of the Boolean returned
5561   |   by ARI_CONFIG.save_payment_instrument_info.
5562   |
5563   | PSEUDO CODE/LOGIC
5564   |
5565   | PARAMETERS
5566   |
5567   | KNOWN ISSUES
5568   |
5569   |
5570   |
5571   | NOTES
5572   |
5573   |
5574   |
5575   | MODIFICATION HISTORY
5576   | Date          Author       Description of Changes
5577   | 29-APR-2004   vnb          Created
5578   | 21-SEP-2004   vnb          Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.save_payment_instrument_info
5579   +============================================================*/
5580  FUNCTION save_payment_inst_info_wrapper ( p_customer_id          IN VARCHAR2,
5581                                            p_customer_site_use_id IN VARCHAR2 DEFAULT NULL)
5582  RETURN VARCHAR2 IS
5583  l_save_payment_inst_flag VARCHAR2(6);
5584  BEGIN
5585     -- Bug 3886652 - Customer Id and Customer Site Use Id added as params to ARI_CONFIG.save_payment_instrument_info
5586     if (ARI_UTILITIES.save_payment_instrument_info(p_customer_id, nvl(p_customer_site_use_id,-1))) then
5587         l_save_payment_inst_flag := 'true';
5588     else
5589         l_save_payment_inst_flag := 'false';
5590     end if;
5591 
5592     return l_save_payment_inst_flag;
5593 
5594  END save_payment_inst_info_wrapper;
5595 
5596  /*============================================================
5597   | PUBLIC function is_grace_days_enabled_wrapper
5598   |
5599   | DESCRIPTION
5600   |   This is a wrapper to return a VARCHAR2 instead of the Boolean returned
5601   |   by ARI_CONFIG.is_discount_grace_days_enabled.
5602   |
5603   | PSEUDO CODE/LOGIC
5604   |
5605   | PARAMETERS
5606   |
5607   | KNOWN ISSUES
5608   |
5609   |
5610   |
5611   | NOTES
5612   |
5613   |
5614   |
5615   | MODIFICATION HISTORY
5616   | Date          Author       Description of Changes
5617   | 28-APR-2004   vnb          Created
5618   +============================================================*/
5619  FUNCTION is_grace_days_enabled_wrapper RETURN VARCHAR2 IS
5620  l_grace_days_flag VARCHAR2(2);
5621  BEGIN
5622     if (ARI_UTILITIES.is_discount_grace_days_enabled) then
5623         l_grace_days_flag := 'Y';
5624     else
5625         l_grace_days_flag := 'N';
5626     end if;
5627 
5628     return l_grace_days_flag;
5629 
5630   END is_grace_days_enabled_wrapper;
5631 
5632 /*============================================================
5633   | PUBLIC function get_discount_wrapper
5634   |
5635   | DESCRIPTION
5636   |   This is a function that is a wrapper to call the AR API for calculating
5637   |   discounts.
5638   |
5639   | PSEUDO CODE/LOGIC
5640   |
5641   | PARAMETERS
5642   |
5643   | KNOWN ISSUES
5644   |
5645   |
5646   |
5647   | NOTES
5648   |
5649   |
5650   |
5651   | MODIFICATION HISTORY
5652   | Date          Author       Description of Changes
5653   | 19-JUL-2004   vnb          Created
5654   +============================================================*/
5655 FUNCTION get_discount_wrapper ( p_ps_id	  IN ar_payment_schedules.payment_schedule_id%TYPE,
5656                                  p_in_applied_amount IN NUMBER) RETURN NUMBER IS
5657     l_discount_amount NUMBER;
5658     l_customer_id     NUMBER;
5659     l_customer_site_use_id NUMBER;
5660     l_rem_amt_rcpt    NUMBER;
5661     l_rem_amt_inv     NUMBER;
5662     l_grace_days_flag VARCHAR2(2);
5663   BEGIN
5664     SELECT CUSTOMER_ID, CUSTOMER_SITE_USE_ID
5665     INTO  l_customer_id, l_customer_site_use_id
5666     FROM  ar_payment_schedules
5667     WHERE PAYMENT_SCHEDULE_ID = p_ps_id;
5668 
5669      -- Check if grace days have to be considered for discount.
5670      --l_grace_days_flag := is_grace_days_enabled_wrapper();
5671      l_grace_days_flag := ARI_UTILITIES.is_discount_grace_days_enabled(l_customer_id,l_customer_site_use_id);
5672 
5673      arp_discounts_api.get_discount(p_ps_id	            => p_ps_id,
5674 		                           p_apply_date	        => trunc(sysdate),
5675                             	   p_in_applied_amount  => p_in_applied_amount,
5676 		                           p_grace_days_flag    => l_grace_days_flag,
5677 		                           p_out_discount       => l_discount_amount,
5678 		                           p_out_rem_amt_rcpt 	=> l_rem_amt_rcpt,
5679 		                           p_out_rem_amt_inv 	=> l_rem_amt_inv);
5680 
5681      return l_discount_amount;
5682 
5683   EXCEPTION
5684     when others then
5685         begin
5686             l_discount_amount := 0;
5687             write_debug_and_log('Unexpected Exception while calculating discount');
5688             write_debug_and_log('- Payment Schedule Id: '||p_ps_id);
5689             write_debug_and_log(SQLERRM);
5690             return l_discount_amount;
5691         end;
5692   END;
5693 
5694 /*============================================================
5695   | PUBLIC function write_error_messages
5696   |
5697   | DESCRIPTION
5698   |   This is a procedure that reads and returns the error messages
5699   |   from the message stack.
5700   |
5701   | PSEUDO CODE/LOGIC
5702   |
5703   | PARAMETERS
5704   |
5705   | KNOWN ISSUES
5706   |
5707   |
5708   |
5709   | NOTES
5710   |
5711   |
5712   |
5713   | MODIFICATION HISTORY
5714   | Date          Author       Description of Changes
5715   | 23-JUL-2004   vnb          Created
5716   +============================================================*/
5717   PROCEDURE write_error_messages (  p_msg_data IN OUT NOCOPY VARCHAR2,
5718                                     p_msg_count IN OUT NOCOPY NUMBER) IS
5719 
5720   l_msg_data VARCHAR2(2000);
5721 
5722   BEGIN
5723         p_msg_data := p_msg_data || '*';
5724         p_msg_count := 0;
5725         LOOP
5726             l_msg_data:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_FALSE);
5727             IF (l_msg_data IS NULL)THEN
5728                 l_msg_data:=FND_MSG_PUB.GET(p_encoded=>FND_API.G_TRUE);
5729                 IF (l_msg_data IS NULL)THEN
5730                     EXIT;
5731                 END IF;
5732                             END IF;
5733             p_msg_data := p_msg_data || l_msg_data || '*';
5734             p_msg_count := p_msg_count + 1;
5735 	    write_debug_and_log(l_msg_data);
5736         END LOOP;
5737   END;
5738 
5739   /*=====================================================================
5740  | PROCEDURE reset_payment_amounts
5741  |
5742  | DESCRIPTION
5743  |   This function will reset the payment amounts on the Payment GT
5744  |   when the user clicks 'Reset to Defaults' button on Advanced Payment page
5745  |
5746  | PARAMETERS
5747  |   p_customer_id	   IN     NUMBER
5748  |   p_site_use_id     IN     NUMBER DEFAULT NULL
5749  |
5750  | HISTORY
5751  |   20-JAN-2005     vnb      Created
5752  |
5753  +=====================================================================*/
5754  PROCEDURE reset_payment_amounts (  p_customer_id		    IN NUMBER,
5755                                     p_site_use_id          IN NUMBER DEFAULT NULL)
5756  IS
5757     l_total_service_charge     NUMBER;
5758     l_procedure_name           VARCHAR2(50);
5759     l_debug_info               VARCHAR2(200);
5760 
5761  BEGIN
5762     --Assign default values
5763     l_total_service_charge     := 0;
5764     l_procedure_name          := '.reset_payment_amounts';
5765 
5766     SAVEPOINT reset_payment_amounts_sp;
5767     -----------------------------------------------------------------------------------------
5768     l_debug_info := 'Update transaction list with original discount and payment amount';
5769     -----------------------------------------------------------------------------------------
5770     IF (PG_DEBUG = 'Y') THEN
5771        arp_standard.debug(l_debug_info);
5772     END IF;
5773     --Striping by currency code is not required because
5774     --it is not possible to navigate to Payment page with multiple currencies
5775     --in the Transaction List for a cusomer context
5776     UPDATE AR_IREC_PAYMENT_LIST_GT
5777     SET discount_amount = original_discount_amt,
5778 	    payment_amt = amount_due_remaining - original_discount_amt - nvl(dispute_amt,0)
5779     WHERE customer_id = p_customer_id
5780     AND   customer_site_use_id = nvl(decode(p_site_use_id, -1, null, p_site_use_id),customer_site_use_id);
5781 
5782     -----------------------------------------------------------------------------------------
5783     l_debug_info := 'Compute service charge';
5784     -----------------------------------------------------------------------------------------
5785     IF (PG_DEBUG = 'Y') THEN
5786        arp_standard.debug(l_debug_info);
5787     END IF;
5788     l_total_service_charge := get_service_charge(p_customer_id, p_site_use_id);
5789 
5790     COMMIT;
5791 
5792  EXCEPTION
5793     WHEN OTHERS THEN
5794         write_debug_and_log('Unexpected Exception while resetting payment and discount amounts');
5795         write_debug_and_log('- Customer Id: '||p_customer_id);
5796         write_debug_and_log('- Customer Site Id: '||p_site_use_id);
5797         write_debug_and_log('- Total Service charge: '||l_total_service_charge);
5798         write_debug_and_log(SQLERRM);
5799 
5800         ROLLBACK TO reset_payment_amounts_sp;
5801 
5802  END reset_payment_amounts;
5803 
5804 
5805 /*=====================================================================
5806  | FUNCTION get_pymt_amnt_due_remaining
5807  |
5808  | DESCRIPTION
5809  |   This function will calculate the remianing amount for a
5810  |   payment that has been selected for apply credit andd return the
5811  |   total amount dure remaining that can be applied.
5812  |
5813  | HISTORY
5814  |
5815  +=====================================================================*/
5816  FUNCTION get_pymt_amnt_due_remaining (  p_cash_receipt_id    IN NUMBER) RETURN NUMBER IS
5817 
5818  l_amount_due_remaining NUMBER ;
5819 
5820  BEGIN
5821   select - sum(app.amount_applied) INTO l_amount_due_remaining
5822              	        from ar_receivable_applications app
5823 	                    where nvl( app.confirmed_flag, 'Y' ) = 'Y'
5824                         AND app.status = 'UNAPP'
5825                         AND app.cash_receipt_id = p_cash_receipt_id;
5826 
5827    RETURN l_amount_due_remaining;
5828 
5829   END get_pymt_amnt_due_remaining;
5830 
5831 /*============================================================
5832  | procedure update_cc_bill_to_site
5833  |
5834  | DESCRIPTION
5835  |   Creates/Updates Credit card bill to location with the given details
5836  |
5837  | PSEUDO CODE/LOGIC
5838  |
5839  | PARAMETERS
5840  |
5841  | KNOWN ISSUES
5842  |
5843  |
5844  |
5845  | NOTES
5846  |
5847  |
5848  |
5849  | MODIFICATION HISTORY
5850  | Date          Author       Description of Changes
5851  | 17-Aug-2005   rsinthre     Created
5852  +============================================================*/
5853   PROCEDURE update_cc_bill_to_site(
5854 		p_cc_location_rec	IN   HZ_LOCATION_V2PUB.LOCATION_REC_TYPE,
5855 		x_cc_bill_to_site_id	IN  NUMBER,
5856 		x_return_status		OUT NOCOPY VARCHAR2,
5857 		x_msg_count		OUT NOCOPY NUMBER,
5858 		x_msg_data		OUT NOCOPY VARCHAR2) IS
5859 
5860 l_location_id			NUMBER(15,0);
5861 l_location_rec			HZ_LOCATION_V2PUB.LOCATION_REC_TYPE;
5862 l_party_site_rec		HZ_PARTY_SITE_V2PUB.party_site_rec_type;
5863 l_party_site_number		VARCHAR2(30);
5864 l_object_version_number		NUMBER(15,0);
5865 
5866 CURSOR location_id_cur IS
5867 	select hps.location_id, hl.object_version_number
5868 	from hz_party_sites hps, hz_locations hl
5869 	where party_site_id = x_cc_bill_to_site_id
5870 	and hps.location_id = hl.location_id;
5871 
5872 location_id_rec	location_id_cur%ROWTYPE;
5873 
5874 l_procedure_name		VARCHAR2(30);
5875 l_debug_info	 	        VARCHAR2(200);
5876 
5877 BEGIN
5878 	l_procedure_name  := '.update_cc_bill_to_site';
5879 -----------------------------------------------------------------------------------------
5880   l_debug_info := 'Call TCA update location - update_location - to update location for CC';
5881 -----------------------------------------------------------------------------------------
5882           write_debug_and_log('Site_id_to_update'|| x_cc_bill_to_site_id);
5883 
5884 --Get LocationId from PartySiteId and update the location
5885 		OPEN location_id_cur;
5886 		FETCH location_id_cur INTO location_id_rec;
5887 		IF(location_id_cur%FOUND) THEN
5888 			l_location_id		:= location_id_rec.location_id;
5889 			l_object_version_number	:= location_id_rec.object_version_number;
5890 		ELSE
5891 		   write_debug_and_log('No Location found for site:'||x_cc_bill_to_site_id );
5892 		   x_return_status := FND_API.G_RET_STS_ERROR;
5893 		   write_error_messages(x_msg_data, x_msg_count);
5894 		   RETURN;
5895 		END IF;
5896 		CLOSE location_id_cur;
5897 
5898 		write_debug_and_log('Loaction id to update:'|| l_location_id);
5899 
5900 		l_location_rec.location_id	:= l_location_id;
5901 		l_location_rec.country		:= p_cc_location_rec.country;
5902 		l_location_rec.address1		:= p_cc_location_rec.address1;
5903 		l_location_rec.address2		:= p_cc_location_rec.address2;
5904 		l_location_rec.address3		:= p_cc_location_rec.address3;
5905 		l_location_rec.city		:= p_cc_location_rec.city;
5906 		l_location_rec.postal_code	:= p_cc_location_rec.postal_code;
5907 		l_location_rec.state		:= p_cc_location_rec.state;
5908 		l_location_rec.county		:= p_cc_location_rec.county;
5909 
5910 		HZ_LOCATION_V2PUB.update_location(
5911 		p_init_msg_list             => FND_API.G_TRUE,
5912 		p_location_rec              => l_location_rec,
5913 		p_object_version_number     => l_object_version_number,
5914 		x_return_status             => x_return_status,
5915 		x_msg_count                 => x_msg_count,
5916 		x_msg_data                  => x_msg_data);
5917 
5918 		IF ( x_return_status <> FND_API.G_RET_STS_SUCCESS ) THEN
5919 	          x_return_status := FND_API.G_RET_STS_ERROR;
5920 	          write_error_messages(x_msg_data, x_msg_count);
5921 	          RETURN;
5922 		END IF;
5923 
5924 EXCEPTION
5925     WHEN OTHERS THEN
5926 	    x_return_status := FND_API.G_RET_STS_ERROR;
5927 
5928             write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
5929 
5930 	    write_debug_and_log('l_location_id'|| l_location_id);
5931             write_debug_and_log('- Return Status: '||x_return_status);
5932             write_debug_and_log(SQLERRM);
5933 
5934             FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
5935             FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
5936             FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
5937             FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
5938             FND_MSG_PUB.ADD;
5939 
5940 END update_cc_bill_to_site;
5941 
5942  /*=====================================================================
5943  | PROCEDURE get_payment_channel_attribs
5944  |
5945  | DESCRIPTION
5946  |   Gets payment channel attribute usages
5947  |
5948  | PARAMETERS
5949  |   p_channel_code	IN  	    VARCHAR2
5950  |   x_return_status 	OUT NOCOPY  VARCHAR2
5951  |   x_cvv_use 		OUT NOCOPY  VARCHAR2
5952  |   x_billing_addr_use	OUT NOCOPY  VARCHAR2
5953  |   x_msg_count        OUT NOCOPY  NUMBER
5954  |   x_msg_data         OUT NOCOPY  VARCHAR2
5955  |
5956  | HISTORY
5957  |   20-SEP-2006     abathini      Created
5958  |
5959  +=====================================================================*/
5960 PROCEDURE get_payment_channel_attribs(	p_channel_code 		IN 	    VARCHAR2,
5961 					x_return_status 	OUT NOCOPY  VARCHAR2,
5962 					x_cvv_use 		OUT NOCOPY  VARCHAR2,
5963 					x_billing_addr_use	OUT NOCOPY  VARCHAR2,
5964 					x_msg_count           	OUT NOCOPY  NUMBER,
5965 					x_msg_data            	OUT NOCOPY  VARCHAR2
5966 				     )
5967 IS
5968 useRecType IBY_FNDCPT_SETUP_PUB.PmtChannel_AttribUses_rec_type;
5969 resRecType IBY_FNDCPT_COMMON_PUB.Result_rec_type;
5970 l_procedure_name		VARCHAR2(50);
5971 l_debug_info	 	        VARCHAR2(200);
5972 BEGIN
5973 
5974  l_procedure_name := '.get_payment_channel_attribs';
5975  -----------------------------------------------------------------------------------------
5976  l_debug_info := 'Call IBY_FNDCPT_SETUP_PUB.Get_Payment_Channel_Attribs - to get payment channel attribute usages';
5977  -----------------------------------------------------------------------------------------
5978     IBY_FNDCPT_SETUP_PUB.Get_Payment_Channel_Attribs
5979     (
5980             p_api_version 		=> 1.0,
5981             x_return_status 	=> x_return_status,
5982             x_msg_count 		=> x_msg_count,
5983             x_msg_data 		=> x_msg_data,
5984             p_channel_code 		=> p_channel_code,
5985             x_channel_attrib_uses	=> useRecType,
5986             x_response 		=> resRecType
5987     );
5988 
5989     x_cvv_use := useRecType.Instr_SecCode_Use;
5990     x_billing_addr_use := useRecType.Instr_Billing_Address;
5991 
5992 EXCEPTION
5993     WHEN OTHERS THEN
5994 	    x_return_status := FND_API.G_RET_STS_ERROR;
5995 
5996             write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
5997 
5998 	    write_debug_and_log('p_channel_code'|| p_channel_code);
5999             write_debug_and_log('- Return Status: '||x_return_status);
6000             write_debug_and_log(SQLERRM);
6001 
6002             FND_MESSAGE.SET_NAME ('AR','ARI_REG_DISPLAY_UNEXP_ERROR');
6003             FND_MESSAGE.SET_TOKEN('PROCEDURE', G_PKG_NAME || l_procedure_name);
6004             FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
6005             FND_MESSAGE.SET_TOKEN('DEBUG_INFO', l_debug_info);
6006             FND_MSG_PUB.ADD;
6007 END get_payment_channel_attribs;
6008 
6009 /*=====================================================================
6010  | PROCEDURE update_invoice_payment_status
6011  |
6012  | DESCRIPTION
6013  |   This procedure will update the PAYMENT_APPROVAL column in ar_payment_schedules
6014  |   with the value p_inv_pay_status for the records in p_payment_schedule_id_list
6015  |
6016  | PARAMETERS
6017  |   p_payment_schedule_id_list	   IN     Inv_list_table_type
6018  |   p_inv_pay_status     		   IN     VARCHAR2
6019  |
6020  | HISTORY
6021  |   17-FEB-2007     abathini      	   Created
6022  |
6023  +=====================================================================*/
6024 
6025 PROCEDURE update_invoice_payment_status( p_payment_schedule_id_list	IN Inv_list_table_type,
6026                                  	     p_inv_pay_status			IN VARCHAR2,
6027                                  	     x_return_status			OUT  NOCOPY VARCHAR2,
6028 				                 x_msg_count            		OUT  NOCOPY NUMBER,
6029 				                 x_msg_data             		OUT  NOCOPY VARCHAR2
6030                                  ) IS
6031 
6032 l_last_update_login		NUMBER(15);
6033 l_last_update_date		DATE;
6034 l_last_updated_by		NUMBER(15);
6035 
6036 BEGIN
6037 
6038     l_last_update_login     := FND_GLOBAL.LOGIN_ID;
6039     l_last_update_date      := sysdate;
6040     l_last_updated_by       := FND_GLOBAL.USER_ID;
6041 
6042    FORALL trx
6043     IN p_payment_schedule_id_list.first .. p_payment_schedule_id_list.last
6044     UPDATE AR_PAYMENT_SCHEDULES set PAYMENT_APPROVAL =  p_inv_pay_status,
6045     LAST_UPDATE_DATE = l_last_update_date, LAST_UPDATED_BY = l_last_updated_by,
6046     LAST_UPDATE_LOGIN = l_last_update_login
6047     where payment_schedule_id = p_payment_schedule_id_list(trx);
6048 
6049     x_return_status := FND_API.G_RET_STS_SUCCESS;
6050     x_msg_count := 0;
6051 
6052 EXCEPTION
6053     WHEN OTHERS THEN
6054       x_return_status := FND_API.G_RET_STS_ERROR;
6055       FND_MSG_PUB.count_and_get(p_encoded => fnd_api.g_false,
6056                                 p_count => x_msg_count,
6057                                 p_data  => x_msg_data);
6058 
6059 END update_invoice_payment_status;
6060 
6061 /*=====================================================================
6062  | FUNCTION get_customer_site_use_id
6063  |
6064  | DESCRIPTION
6065  | This function checks if the user has access to the primary bill to site
6066  | of the customer. If yes, then returns that site id.
6067  | else, checks if the transactions selected by the user belongs
6068  | to a same site. If yes, then return that site id else, returns -1.
6069  |
6070  | PARAMETERS
6071  |   p_session_id  IN   NUMBER
6072  |   p_customer_id IN   NUMBER
6073  |
6074  | RETURN
6075  |   l_customer_site_use_id  NUMBER
6076  | HISTORY
6077  |   29-Oct-2009     rsinthre              Created
6078  |
6079  +=====================================================================*/
6080 
6081  FUNCTION get_customer_site_use_id (p_session_id IN NUMBER,
6082                                     p_customer_id IN NUMBER
6083                                    )
6084 				 RETURN NUMBER
6085  IS
6086 
6087  l_customer_site_use_id  NUMBER;
6088  l_debug_info		 VARCHAR2(200);
6089  l_procedure_name 	 VARCHAR2(30);
6090 
6091  e_no_rows_in_GT EXCEPTION;
6092 
6093  CURSOR get_cust_site_use_id_cur IS
6094 	SELECT DISTINCT pay_for_customer_site_id
6095 	FROM   ar_irec_payment_list_gt
6096 	WHERE  customer_id = p_customer_id;
6097 
6098  BEGIN
6099 
6100   l_procedure_name := '.get_customer_site_use_id';
6101   l_customer_site_use_id := NULL;
6102 
6103   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
6104 	  fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name, 'Begin+');
6105 	  fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,
6106             'p_session_id=' || p_session_id ||
6107             'p_user_id=' || FND_GLOBAL.user_id ||
6108             'p_customer_id=' || p_customer_id);
6109   end if;
6110 
6111 
6112   ---------------------------------------------------------------------------
6113   l_debug_info := 'Check if the user has access to the primary bill to site id';
6114   ---------------------------------------------------------------------------
6115   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
6116 	 fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,l_debug_info);
6117   end if;
6118 
6119   BEGIN
6120 
6121       SELECT  usite.customer_site_use_id
6122       INTO    l_customer_site_use_id
6123       FROM    ar_irec_user_acct_sites_all usite,
6124               hz_cust_site_uses hzcsite
6125       WHERE
6126       usite.session_id 	    =	p_session_id
6127       AND usite.customer_id	    =	p_customer_id
6128       AND usite.user_id 	    =	FND_GLOBAL.user_id
6129       AND hzcsite.site_use_id   =	usite.customer_site_use_id
6130       AND hzcsite.primary_flag  =	'Y'
6131       AND hzcsite.site_use_code =	'BILL_TO'
6132       AND hzcsite.status 	    =	'A' ;
6133   EXCEPTION
6134 	WHEN NO_DATA_FOUND THEN
6135 	l_customer_site_use_id := NULL;
6136   END;
6137 
6138   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
6139 	 fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Check for acess to the Primary bill to site returned site id=' || l_customer_site_use_id);
6140   end if;
6141 
6142   IF (l_customer_site_use_id IS NULL) THEN
6143   /* So, user does not have access to primary bill to site
6144     Check, if the selected transactions belong to a same site. If yes, then return that site id else return -1.
6145   */
6146      OPEN get_cust_site_use_id_cur;
6147      LOOP
6148           FETCH get_cust_site_use_id_cur INTO l_customer_site_use_id ;
6149 
6150           IF get_cust_site_use_id_cur%ROWCOUNT >1 THEN
6151                if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
6152                   fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'The selected transactions belong to more than one site');
6153                end if;
6154               l_customer_site_use_id := -1;
6155               EXIT;
6156           ELSIF get_cust_site_use_id_cur%ROWCOUNT = 0 THEN
6157                if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
6158                   fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Query on ar_irec_payment_list_gt returned 0 rows');
6159                end if;
6160                RAISE e_no_rows_in_GT;
6161                EXIT;
6162           END IF;
6163 
6164           EXIT WHEN get_cust_site_use_id_cur%NOTFOUND OR get_cust_site_use_id_cur%NOTFOUND IS NULL;
6165      END LOOP;
6166      CLOSE get_cust_site_use_id_cur;
6167 
6168   END IF;
6169 
6170   if( FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL ) then
6171       fnd_log.string(fnd_log.LEVEL_STATEMENT,G_PKG_NAME||l_procedure_name,'Return val: l_customer_site_use_id=' || l_customer_site_use_id);
6172   end if;
6173 
6174  RETURN l_customer_site_use_id;
6175 
6176  EXCEPTION
6177     WHEN e_no_rows_in_GT THEN
6178       write_debug_and_log('No rows present in ar_irec_payment_list_gt for the given customer in ' || G_PKG_NAME || l_procedure_name);
6179       write_debug_and_log('p_session_id: '|| p_session_id);
6180       write_debug_and_log('p_user_id: '|| FND_GLOBAL.user_id);
6181       write_debug_and_log('p_customer_id: '|| p_customer_id);
6182 
6183     WHEN OTHERS THEN
6184       write_debug_and_log('Unexpected Exception in ' || G_PKG_NAME || l_procedure_name);
6185       write_debug_and_log('ERROR =>'|| SQLERRM);
6186       write_debug_and_log('p_session_id: '|| p_session_id);
6187       write_debug_and_log('p_user_id: '|| FND_GLOBAL.user_id);
6188       write_debug_and_log('p_customer_id: '|| p_customer_id);
6189 
6190 
6191  END get_customer_site_use_id;
6192 
6193 END AR_IREC_PAYMENTS;