DBA Data[Home] [Help]

PACKAGE BODY: APPS.ARP_BR_HOUSEKEEPER_PKG

Source


1 PACKAGE BODY arp_br_housekeeper_pkg AS
2 /* $Header: ARRBRHKB.pls 120.6 2005/06/03 20:41:32 vcrisost ship $ */
3 
4 
5 /*----------------------------------------------------+
6  | Package global record (private) for BR information |
7  +----------------------------------------------------*/
8 TYPE BR_rec_type IS RECORD (
9     customer_trx_id              ar_payment_schedules.customer_trx_id%TYPE,
10     payment_schedule_id          ar_payment_schedules.payment_schedule_id%TYPE,
11     maturity_date                ar_payment_schedules.due_date%TYPE,
12     reserved_type                ar_payment_schedules.reserved_type%TYPE,
13     reserved_value               ar_payment_schedules.reserved_value%TYPE,
14     amount_due_remaining         ar_payment_schedules.amount_due_remaining%TYPE,
15     tax_remaining                ar_payment_schedules.tax_remaining%TYPE,
16     gl_date                      ar_transaction_history.gl_date%TYPE,
17     transaction_history_id       ar_transaction_history.transaction_history_id%TYPE,
18     prv_trx_history_id           ar_transaction_history.prv_trx_history_id%TYPE,
19     status                       ar_transaction_history.status%TYPE,
20     event                        ar_transaction_history.event%TYPE,
21     org_id                       ar_transaction_history.org_id%TYPE);
22 
23 /*-----------------------------------------------------------------+
24  | Package global variables (private) to be used in sub procedures |
25  +-----------------------------------------------------------------*/
26 pg_gl_date                      DATE;
27 pg_effective_date               DATE;
28 pg_deferred_tax_exists          BOOLEAN := TRUE;
29 pg_collection_days              ar_receipt_method_accounts.br_collection_days%TYPE;
30 pg_risk_elimination_days        ar_receipt_method_accounts.risk_elimination_days%TYPE;
31 pg_rct_inherit_inv_num_flag     ar_receipt_methods.receipt_inherit_inv_num_flag%TYPE;
32 pg_receipt_method_id            ar_batches.receipt_method_id%TYPE;
33 pg_remit_bank_acct_use_id       ar_batches.remit_bank_acct_use_id%type;
34 pg_remittance_batch_date        ar_batches.batch_date%TYPE;
35 pg_endorsement_date             DATE;
36 pg_called_from                  VARCHAR2(50);
37 
38 pg_BR_rec                       BR_rec_type;
39 
40 
41 /*--------------------------+
42  | Exception for API errors |
43  +--------------------------*/
44 API_exception                   EXCEPTION;
45 
46 PG_DEBUG varchar2(1) := NVL(FND_PROFILE.value('AFLOG_ENABLED'), 'N');
47 
48 procedure create_and_apply_Receipt(p_move_deferred_tax         IN VARCHAR2 DEFAULT 'Y',
49                                    p_receipt_date              IN DATE);
50 
51 procedure approve_Adjustment(p_adjustment_rec    IN OUT NOCOPY ar_adjustments%ROWTYPE,
52                              p_move_deferred_tax IN     VARCHAR2 DEFAULT 'Y');
53 
54 procedure apply_Receipt(p_move_deferred_tax         IN VARCHAR2 DEFAULT 'Y',
55                         p_receipt_date              IN DATE);
56 
57 procedure create_maturity_date_event(p_move_deferred_tax IN VARCHAR2 DEFAULT 'Y',
58                                      p_event_date        DATE);
59 
60 PROCEDURE prev_posted_trh(p_transaction_history_id IN  ar_transaction_history.transaction_history_id%TYPE,
61                           p_trh_rec                OUT NOCOPY ar_transaction_history%ROWTYPE);
62 
63 PROCEDURE fetch_remittance_setup_data(p_status             IN ar_transaction_history.status%TYPE,
64                                       p_batch_id           IN ar_batches.batch_id%TYPE DEFAULT NULL);
65 
66 PROCEDURE fetch_endorsement_setup_data(p_receivables_trx_id IN ar_receivables_trx.receivables_trx_id%TYPE);
67 
68 PROCEDURE process_standard_remitted;
69 PROCEDURE process_factored;
70 PROCEDURE process_endorsed;
71 
72 PROCEDURE write_API_output(p_msg_count        IN NUMBER,
73                            p_msg_data         IN VARCHAR2);
74 
75 PROCEDURE write_debug_and_log(p_message IN VARCHAR2);
76 
77 FUNCTION validate_and_default_gl_date(p_gl_date                in date,
78                                       p_doc_date               in date,
79                                       p_validation_date1       in date,
80                                       p_validation_date2       in date,
81                                       p_validation_date3       in date,
82                                       p_default_date1          in date,
83                                       p_default_date2          in date,
84                                       p_default_date3          in date) RETURN DATE;
85 
86 FUNCTION validate_against_doc_gl_date(p_gl_date                in date,
87                                       p_doc_gl_date            in date) RETURN DATE;
88 
89 /*===========================================================================+
90  | PROCEDURE ar_br_housekeeper                                               |
91  |    	                                                                     |
92  | DESCRIPTION                                                               |
93  |    Loops through matured Bills Receivable documents and creates maturity  |
94  |    and /or payment events depending on the given parameters.              |
95  |                                                                           |
96  | SCOPE - PUBLIC                                                            |
97  |                                                                           |
98  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
99  |    arp_util.debug                                                         |
100  |                                                                           |
101  | ARGUMENTS  : IN:                                                          |
102  |              OUT:                                                         |
103  |          IN/ OUT:                                                         |
104  |                                                                           |
105  | RETURNS    : NONE                                                         |
106  |                                                                           |
107  | MODIFICATION HISTORY                                                      |
108  |     17-APR-2000  Jani Rautiainen      Created                             |
109  |                                                                           |
110  +===========================================================================*/
111 function ar_br_housekeeper(p_effective_date          IN DATE,
112                            p_gl_date                 IN DATE,
113                            p_maturity_date_low       IN DATE,
114                            p_maturity_date_high      IN DATE,
115                            p_trx_gl_date_low         IN DATE,
116                            p_trx_gl_date_high        IN DATE,
117                            p_cust_trx_type_id        IN ra_cust_trx_types.cust_trx_type_id%TYPE,
118                            p_include_factored_BR     IN VARCHAR2 DEFAULT 'Y',
119                            p_include_std_remitted_BR IN VARCHAR2 DEFAULT 'Y',
120                            p_include_endorsed_BR     IN VARCHAR2 DEFAULT 'Y') RETURN BOOLEAN IS
121 
122  /*--------------------------------------+
123   | Cursor for matured BR transactions   |
124   +--------------------------------------*/
125   CURSOR matured_cur IS
126     select ps.customer_trx_id,
127            ps.payment_schedule_id,
128            ps.due_date maturity_date,
129            ps.reserved_type,
130            ps.reserved_value,
131            ps.amount_due_remaining,
132            ps.tax_remaining,
133            trh.gl_date,
134            trh.transaction_history_id,
135            trh.prv_trx_history_id,
136            trh.status,
137            trh.event,
138            ps.org_id
139     from ar_transaction_history trh, ar_payment_schedules ps
140     where
141     /*-----------------------------------------------------+
142      | Restrict the transaction type if given as parameter |
143      +-----------------------------------------------------*/
144           ps.cust_trx_type_id   = NVL(p_cust_trx_type_id,ps.cust_trx_type_id)
145     and   ps.class              = 'BR'
146     and   ps.reserved_type      in ('REMITTANCE','ADJUSTMENT')
147 
148     /*---------------------------------------------------------------------------------+
149      | Restrict the maturity date to be earlier than effective_date given as parameter |
150      +---------------------------------------------------------------------------------*/
151     and   trunc(ps.due_date) <= trunc(NVL(p_effective_date, SYSDATE))
152 
153     /*--------------------------------------------------------------------------------+
154      | Restrict the maturity date to be within maturity date range given as parameter |
155      +--------------------------------------------------------------------------------*/
156     and   trunc(ps.due_date) between trunc(NVL(p_maturity_date_low ,ps.due_date))
157                         and   trunc(NVL(p_maturity_date_high,ps.due_date))
158 
159     /*--------------------------------------------------------------------------------+
160      | Restrict the transaction GL date to be within GL date range given as parameter |
161      +--------------------------------------------------------------------------------*/
162     and   trunc(ps.gl_date) between trunc(NVL(p_trx_gl_date_low ,ps.gl_date))
163                        and   trunc(NVL(p_trx_gl_date_high,ps.gl_date))
164     and   ps.customer_trx_id = trh.customer_trx_id
165     and   trh.current_record_flag = 'Y'
166     /*-------------------------------------------------------------------------------------------------------------------+
167      | Restrict the BR status depending on flags given as parameter.                                                     |
168      | If p_include_std_remitted_BR = 'Y' then BRs with status 'REMITTED' are included                                   |
169      | If p_include_factored_BR = 'Y' then BRs with statuses 'FACTORED' and 'MATURED_PEND_RISK_ELIMINATION' are included |
170      | If p_include_endorsed_BR = 'Y' then BRs with status 'ENDORSED' are included                                       |
171      | If all or some of the flags are 'Y' then the corresponding statuses are included                                  |
172      +-------------------------------------------------------------------------------------------------------------------*/
173     and   trh.status in (decode(NVL(p_include_std_remitted_BR,'Y'),
174                                     'Y','REMITTED',NULL),
175                          decode(NVL(p_include_factored_BR,'Y'),
176                                     'Y','FACTORED',NULL),
177                          decode(NVL(p_include_factored_BR,'Y'),
178                                     'Y','MATURED_PEND_RISK_ELIMINATION',NULL),
179                          decode(NVL(p_include_endorsed_BR,'Y'),
180                                     'Y','ENDORSED',NULL)
181                          )
182     FOR UPDATE OF ps.reserved_type, trh.status NOWAIT;
183 
184   l_BR_rec                     BR_rec_type;
185   l_default_gl_date            DATE;
186   l_deferred_tax_exists        BOOLEAN := FALSE;
187 
188 BEGIN
189   write_debug_and_log( 'arp_br_housekeeper_pkg.ar_br_housekeeper()+' );
190   write_debug_and_log( 'p_effective_date = '||to_char(p_effective_date));
191   write_debug_and_log( 'p_gl_date = '       ||to_char(p_gl_date));
192   write_debug_and_log( 'p_maturity_date_low = '  ||to_char(p_maturity_date_low));
193   write_debug_and_log( 'p_maturity_date_high = ' ||to_char(p_maturity_date_high));
194   write_debug_and_log( 'p_trx_gl_date_low = '    ||to_char(p_trx_gl_date_low));
195   write_debug_and_log( 'p_trx_gl_date_high = '   ||to_char(p_trx_gl_date_high));
196   write_debug_and_log( 'p_cust_trx_type_id = '   ||to_char(p_cust_trx_type_id));
197   write_debug_and_log( 'p_include_factored_BR = '||p_include_factored_BR);
198   write_debug_and_log( 'p_include_std_remitted_BR = '||p_include_std_remitted_BR);
199   write_debug_and_log( 'p_include_endorsed_BR = '    ||p_include_endorsed_BR);
200 
201  /*------------------------------------------------------------------------+
202   | Validate GL date. If gl_date is not passed try to default it. If given |
203   | GL_date is valid use that If given GL_date is invalid or null then try |
204   | current date If neither the given GL_date nor SYSDATE is valid, then   |
205   | the GL_DATE will be defaulted to the last date of the most recent open |
206   | period.                                                                |
207   +------------------------------------------------------------------------*/
208   l_default_gl_date := arp_br_housekeeper_pkg.validate_and_default_gl_date(p_gl_date,
209                                                                            NULL,NULL,NULL,NULL,
210                                                                            SYSDATE,
211                                                                            NULL,NULL);
212   IF l_default_gl_date is not NULL THEN
213 
214     pg_gl_date := l_default_gl_date;
215     write_debug_and_log( 'pg_gl_date = '||to_char(pg_gl_date));
216 
217   ELSE
218    /*-----------------------------------------------------+
219     | Invalid GL_date and system was unable to default it |
220     +-----------------------------------------------------*/
221     write_debug_and_log( 'Invalid GL date' );
222     RETURN FALSE;
223 
224   END IF;
225 
226  /*----------------------------------------------------------------------------+
227   | Copy gl_date to a package global, so it can be seen form the sub procedures|
228   +----------------------------------------------------------------------------*/
229   pg_effective_date := NVL(p_effective_date,SYSDATE);
230 
231   write_debug_and_log( 'pg_effective_date = '||to_char(pg_effective_date));
232 
233  /*---------------------------------------------------------------------------+
234   | Loop through matured BR transactions. Have to use WHILE loop since the    |
235   | copy to package global record gives error with FOR loop.                  |
236   | ORA-21615: copy of an OTS (named or simple) instance failed               |
237   | ORA-21614: constraint violation for attribute number [6]                  |
238   +---------------------------------------------------------------------------*/
239   OPEN  matured_cur;
240   FETCH matured_cur INTO l_BR_rec;
241 
242  /*---------------------------------------------------------------------------+
243   | If no BRs were selected, write information to the log. The processing will|
244   | skip the loop and exit the program. TRUE is returned as value since no    |
245   | error occurred.                                                           |
246   +---------------------------------------------------------------------------*/
247   IF matured_cur%NOTFOUND THEN
248 
249      write_debug_and_log( 'No Bills Receivable transactions matching the given criteria' );
250 
251   END IF;
252 
253  /*--------------------------------------+
254   | Process the selected BR transactions |
255   +--------------------------------------*/
256   WHILE matured_cur%FOUND LOOP
257 
258    /*-----------------------------------------------------------+
259     | Copy values from local record to a package global record, |
260     | so the values can be seen form the sub procedures         |
261     +-----------------------------------------------------------*/
262     pg_BR_rec := l_BR_rec;
263 
264    /*--------------------------+
265     | Lock rest of the tables  |
266     +--------------------------*/
267     arp_process_br_header.lock_transaction(pg_BR_rec.customer_trx_id);
268 
269     write_debug_and_log( 'pg_BR_rec.customer_trx_id = '       ||to_char(pg_BR_rec.customer_trx_id));
270     write_debug_and_log( 'pg_BR_rec.payment_schedule_id = '   ||to_char(pg_BR_rec.payment_schedule_id));
271     write_debug_and_log( 'pg_BR_rec.maturity_date = '         ||to_char(pg_BR_rec.maturity_date));
272     write_debug_and_log( 'pg_BR_rec.reserved_type = '         ||pg_BR_rec.reserved_type);
273     write_debug_and_log( 'pg_BR_rec.reserved_value = '        ||to_char(pg_BR_rec.reserved_value));
274     write_debug_and_log( 'pg_BR_rec.amount_due_remaining = '  ||to_char(pg_BR_rec.amount_due_remaining));
275     write_debug_and_log( 'pg_BR_rec.tax_remaining = '         ||to_char(pg_BR_rec.tax_remaining));
276     write_debug_and_log( 'pg_BR_rec.gl_date = '               ||to_char(pg_BR_rec.gl_date));
277     write_debug_and_log( 'pg_BR_rec.transaction_history_id = '||to_char(pg_BR_rec.transaction_history_id));
278     write_debug_and_log( 'pg_BR_rec.prv_trx_history_id = '    ||to_char(pg_BR_rec.prv_trx_history_id));
279     write_debug_and_log( 'pg_BR_rec.status = '                ||pg_BR_rec.status);
280     write_debug_and_log( 'pg_BR_rec.event  = '                ||pg_BR_rec.event);
281     write_debug_and_log( 'pg_BR_rec.org_id = '                ||to_char(pg_BR_rec.org_id));
282 
286     +-----------------------------------------------------------*/
283    /*-----------------------------------------------------------+
284     | Check whether tax exists for this BR, this information is |
285     | used when deciding whether to move deferred tax or not    |
287     ARP_PROCESS_BR_HEADER.move_deferred_tax(pg_BR_rec.customer_trx_id,l_deferred_tax_exists);
288 
289     IF l_deferred_tax_exists THEN
290 
291        pg_deferred_tax_exists := TRUE;
292 
293     ELSE
294 
295        pg_deferred_tax_exists := FALSE;
296 
297     END IF;
298 
299    /*--------------------------------------------------+
300     | Based on the status and dates branch the code    |
301     +--------------------------------------------------*/
302 
303     IF pg_BR_rec.status = 'REMITTED' THEN
304 
305       pg_called_from := 'BR_REMITTED';
306       arp_br_housekeeper_pkg.process_standard_remitted;
307 
308     ELSIF pg_BR_rec.status = 'FACTORED' or pg_BR_rec.status = 'MATURED_PEND_RISK_ELIMINATION' THEN
309 
310       pg_called_from := 'BR_FACTORED_WITH_RECOURSE';
311       arp_br_housekeeper_pkg.process_factored;
312 
313     ELSIF pg_BR_rec.status = 'ENDORSED' THEN
314 
315       pg_called_from := NULL;
316       arp_br_housekeeper_pkg.process_endorsed;
317 
318     ELSE
319 
320      /*--------------------------------------------------+
321       | Not supported BR transaction status, this should |
322       | never happen unless the main query is changed    |
323       +--------------------------------------------------*/
324       write_debug_and_log( 'Status '|| pg_BR_rec.status ||' not supported' );
325       APP_EXCEPTION.raise_exception;
326 
327     END IF;
328 
329     FETCH matured_cur INTO l_BR_rec;
330 
331   END LOOP;
332 
333   CLOSE matured_cur;
334 
335   write_debug_and_log( 'arp_br_housekeeper_pkg.ar_br_housekeeper()-' );
336   return(TRUE);
337 
338   EXCEPTION
339   WHEN OTHERS THEN
340         IF matured_cur%ISOPEN THEN
341           CLOSE matured_cur;
342         END IF;
343 	write_debug_and_log('Exception: arp_br_housekeeper_pkg.ar_br_housekeeper '||SQLERRM);
344 	RAISE;
345 
346 END ar_br_housekeeper;
347 
348 
349 /*===========================================================================+
350  | PROCEDURE process_standard_remitted                                       |
351  |    	                                                                     |
352  | DESCRIPTION                                                               |
353  |  This procedure processes standard remitted bills receivable transactions |
354  |                                                                           |
355  | SCOPE - PUBLIC                                                            |
356  |                                                                           |
357  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
358  |    arp_util.debug                                                         |
359  |                                                                           |
360  | ARGUMENTS  : IN:  NONE                                                    |
361  |                                                                           |
362  | RETURNS    : NONE                                                         |
363  |                                                                           |
364  | MODIFICATION HISTORY                                                      |
365  |     30-JUN-2000  Jani Rautiainen      Created                             |
366  |                                                                           |
367  +===========================================================================*/
368 PROCEDURE process_standard_remitted IS
369 
370   l_move_deferred_tax          VARCHAR2(1) := 'Y';
371   l_receipt_date               DATE;
372 
373 BEGIN
374   write_debug_and_log( 'arp_br_housekeeper_pkg.process_standard_remitted()+' );
375 
376  /*-------------------------------------------------+
377   | Fetch information from the BR remittance batch  |
378   | The procedure populates a package global record |
379   | with the data, accessible to all sub procedures |
380   +-------------------------------------------------*/
381   arp_br_housekeeper_pkg.fetch_remittance_setup_data(pg_BR_rec.status,
382                                                      pg_BR_rec.reserved_value);
383 
384  /*--------------------------------------------------------+
385   | Check whether we have remitted after the maturity date |
386   | and branch the code accordingly                        |
387   +--------------------------------------------------------*/
388   IF trunc(pg_remittance_batch_date) >= trunc(pg_BR_rec.maturity_date) THEN
389 
390    /*----------------------------------------------------------------+
391     | Check whether we have passed remittance date + collection_days |
392     | and branch the code accordingly                                |
393     +----------------------------------------------------------------*/
394     IF trunc(pg_effective_date) < (trunc(pg_remittance_batch_date) + NVL(pg_collection_days,0)) THEN
395 
396      /*----------------------------------------------------+
397       | BR was remitted late and remittance has not passed |
398       | collection days, do nothing                        |
399       +----------------------------------------------------*/
403 
400       write_debug_and_log('Bills Receivable was remitted late and remittance has not passed collection days, Bills receivable not processed ');
401 
402     ELSE
404      /*----------------------------------------------------------------+
405       | BR was remitted late and remittance has passed collection days,|
406       | create receipt, apply it and deferred tax is moved as part     |
407       | of the application. Deferred tax is only moved if tax to       |
408       | be moved exists                                                |
409       +----------------------------------------------------------------*/
410       IF pg_deferred_tax_exists THEN
411         l_move_deferred_tax := 'Y';
412       ELSE
413         l_move_deferred_tax := 'N';
414       END IF;
415 
416       l_receipt_date := pg_remittance_batch_date + NVL(pg_collection_days,0);
417       create_and_apply_Receipt(l_move_deferred_tax,l_receipt_date);
418 
419     END IF; /* l_remittance_past_effective */
420 
421   ELSE
422 
423    /*----------------------------------------------------------------+
424     | BR was remitted within maturity, create receipt, apply it and  |
425     | deferred tax is moved as part of the application. Deferred tax |
426     | is only moved if tax to be moved exists                        |
427     +----------------------------------------------------------------*/
428     IF pg_deferred_tax_exists THEN
429       l_move_deferred_tax := 'Y';
430     ELSE
431       l_move_deferred_tax := 'N';
432     END IF;
433 
434     l_receipt_date := pg_BR_rec.maturity_date;
435     create_and_apply_Receipt(l_move_deferred_tax,l_receipt_date);
436 
437   END IF; /* l_remittace_past_maturity */
438 
439   write_debug_and_log( 'arp_br_housekeeper_pkg.process_standard_remitted()-' );
440 
441   EXCEPTION
442     WHEN OTHERS THEN
443       write_debug_and_log('Exception: arp_br_housekeeper_pkg.process_standard_remitted '||SQLERRM);
444       RAISE;
445 END process_standard_remitted;
446 
447 /*===========================================================================+
448  | PROCEDURE process_factored                                                |
449  |    	                                                                     |
450  | DESCRIPTION                                                               |
451  |  This procedure processes factored bills receivable transactions          |
452  |                                                                           |
453  | SCOPE - PUBLIC                                                            |
454  |                                                                           |
455  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
456  |    arp_util.debug                                                         |
457  |                                                                           |
458  | ARGUMENTS  : IN:  NONE                                                    |
459  |                                                                           |
460  | RETURNS    : NONE                                                         |
461  |                                                                           |
462  | MODIFICATION HISTORY                                                      |
463  |     30-JUN-2000  Jani Rautiainen      Created                             |
464  |                                                                           |
465  +===========================================================================*/
466 PROCEDURE process_factored IS
467 
468   l_move_deferred_tax          VARCHAR2(1) := 'Y';
469   prev_trh_rec                 ar_transaction_history%ROWTYPE;
470   l_cutoff_date                DATE;
471   l_remitted_late              BOOLEAN := FALSE;
472   l_event_date                 DATE;
473 
474 BEGIN
475 
476   write_debug_and_log( 'arp_br_housekeeper_pkg.process_factored()+' );
477 
478  /*-------------------------------------------------+
479   | Fetch information from the BR remittance batch  |
480   | The procedure populates a package global record |
481   | with the data, accessible to all sub procedures |
482   +-------------------------------------------------*/
483   arp_br_housekeeper_pkg.fetch_remittance_setup_data(pg_BR_rec.status,
484                                                      pg_BR_rec.reserved_value);
485 
486  /*-------------------------------------------------+
487   | Fetch information on the previous posted        |
488   | transaction record for this BR. This information|
489   | is used to decide what processing is needed for |
490   | the Bills Receivable.                           |
491   +-------------------------------------------------*/
492   arp_br_housekeeper_pkg.prev_posted_trh(pg_BR_rec.transaction_history_id,
493                                          prev_trh_rec);
494 
495  /*--------------------------------------------------------+
496   | Check whether we have remitted after the maturity date |
497   | and branch the code accordingly                        |
498   +--------------------------------------------------------*/
499   IF trunc(pg_remittance_batch_date) >= trunc(pg_BR_rec.maturity_date) THEN
500 
501     l_cutoff_date   := pg_remittance_batch_date;
502     l_remitted_late := TRUE;
503     l_event_date    := pg_remittance_batch_date + NVL(pg_risk_elimination_days,0);
504 
505   ELSE
506     l_cutoff_date   := pg_BR_rec.maturity_date;
507     l_remitted_late := FALSE;
508     l_event_date    := pg_BR_rec.maturity_date;
509   END IF;
510 
514   IF trunc(pg_effective_date) < (trunc(l_cutoff_date) + NVL(pg_risk_elimination_days,0)) THEN
511  /*-------------------------------------------------------------------------------+
512   | Check whether Effective date has passed maturity date + risk elimination days |
513   +-------------------------------------------------------------------------------*/
515 
516    /*---------------------------------------------------------------------+
517     | Effective date has NOT passed maturity date + risk elimination days |
518     +---------------------------------------------------------------------*/
519 
520     IF trunc(pg_effective_date) < trunc(l_cutoff_date) THEN
521 
522      /*------------------------------------------------------------+
523       | Effective date is earlier than the cutoff date, do nothing |
524       +------------------------------------------------------------*/
525       NULL;
526 
527     ELSE
528 
529      /*--------------------------------------------------------+
530       | Effective date is earlier than the cutoff date + risk, |
531       | but later than l_cutoff_date date. Move VAT if needed  |
532       +--------------------------------------------------------*/
533 
534       IF pg_BR_rec.status = 'FACTORED' THEN
535 
536         /*--------------------------------------------------------------+
537          | Bill has matured and maturity event has not yet taken place, |
538          | move deferred tax as part of MATURITY_DATE transaction       |
539          | history record. Deferred tax is only moved if tax to be moved|
540          | exists and the BR was not remitted late                      |
541          +--------------------------------------------------------------*/
542         IF pg_deferred_tax_exists AND NOT l_remitted_late THEN
543           l_move_deferred_tax := 'Y';
544         ELSE
545           l_move_deferred_tax := 'N';
546         END IF;
547 
548         create_maturity_date_event(l_move_deferred_tax,l_event_date);
549 
550       END IF; /* status = FACTORED */
551 
552     END IF; /* cutoff past effective */
553 
554   ELSE
555 
556    /*---------------------------------------------------------------+
557     | Effective date has passed cutoff date + risk elimination days |
558     +---------------------------------------------------------------*/
559    /*---------------------------------------------------------------+
560     | The maturity event has not yet happened, so STD application   |
561     | is reversed and a normal application is done. Deferred Tax is |
562     | moved as part of the application. Deferred tax is only moved  |
563     | if tax to be moved exists. Non-postable maturity date event   |
564     | is created to be consistent                                   |
565     +--------------------------------------------------------------*/
566 
567     IF pg_deferred_tax_exists THEN
568       l_move_deferred_tax := 'Y';
569     ELSE
570       l_move_deferred_tax := 'N';
571     END IF;
572 
573     IF pg_BR_rec.status = 'FACTORED' THEN
574 
575       create_maturity_date_event('N',l_event_date);
576 
577     ELSE /* The status must be Matured pending risk elimination */
578 
579       /*---------------------------------------------------------------+
580        | If maturity date event exists and it was postable, do not move|
581        | deferred tax again                                            |
582        +---------------------------------------------------------------*/
583       IF prev_trh_rec.event = 'MATURITY_DATE' AND prev_trh_rec.postable_flag = 'Y' THEN
584 
585         l_move_deferred_tax := 'N';
586 
587       END IF;
588     END IF;
589 
590    /*---------------------------------------------------------------+
591     | Pass in the apply date for the application. If BR was remitted|
592     | late we use the remittance batch date + risk elimination.     |
593     | Otherwise we use the maturity date.                           |
594     +---------------------------------------------------------------*/
595     apply_Receipt(l_move_deferred_tax,l_event_date);
596 
597   END IF; /* cutoff past risk */
598 
599   write_debug_and_log( 'arp_br_housekeeper_pkg.process_factored()-' );
600 
601   EXCEPTION
602     WHEN OTHERS THEN
603       write_debug_and_log('Exception: arp_br_housekeeper_pkg.process_factored '||SQLERRM);
604       RAISE;
605 
606 END process_factored;
607 
608 /*===========================================================================+
609  | PROCEDURE process_endorsed                                                |
610  |    	                                                                     |
611  | DESCRIPTION                                                               |
612  |  This procedure processes endorsed bills receivable transactions          |
613  |                                                                           |
614  | SCOPE - PUBLIC                                                            |
615  |                                                                           |
616  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
617  |    arp_util.debug                                                         |
618  |                                                                           |
619  | ARGUMENTS  : IN:  NONE                                                    |
620  |                                                                           |
621  | RETURNS    : NONE                                                         |
625  |                                                                           |
622  |                                                                           |
623  | MODIFICATION HISTORY                                                      |
624  |     30-JUN-2000  Jani Rautiainen      Created                             |
626  +===========================================================================*/
627 PROCEDURE process_endorsed IS
628 
629  /*---------------------------------------------+
630   | Cursor to fetch last Endorsement adjustment |
631   +---------------------------------------------*/
632   CURSOR last_adjustment_cur IS
633     select adj.*
634     from ar_adjustments adj
635     where adj.customer_trx_id = pg_BR_rec.customer_trx_id
636     and   adj.status = 'W'
637     order by adj.adjustment_id desc;
638 
639   last_adjustment_rec          ar_adjustments%ROWTYPE;
640 
641   l_move_deferred_tax          VARCHAR2(1) := 'Y';
642   prev_trh_rec                 ar_transaction_history%ROWTYPE;
643 
644 BEGIN
645 
646   write_debug_and_log( 'arp_br_housekeeper_pkg.process_endorsed()+' );
647 
648  /*-----------------------------------+
649   | Fetch last Endorsement adjustment |
650   +-----------------------------------*/
651   OPEN last_adjustment_cur;
652   FETCH last_adjustment_cur INTO last_adjustment_rec;
653 
654    /*---------------------------------------------+
655     | If last Endorsement adjusment is not found, |
656     | stop processing and raise an exception      |
657     +---------------------------------------------*/
658    IF last_adjustment_cur%NOTFOUND THEN
659 
660      write_debug_and_log( 'Last endorsement adjustment for Bills Receivable transaction cannot be found' );
661      CLOSE last_adjustment_cur;
662      APP_EXCEPTION.raise_exception;
663 
664    END IF;
665 
666   CLOSE last_adjustment_cur;
667 
668  /*-------------------------------------------------+
669   | Fetch information from the receivable activity  |
670   | The procedure populates a package global record |
671   | with the data, accessible to all sub procedures |
672   +-------------------------------------------------*/
673   arp_br_housekeeper_pkg.fetch_endorsement_setup_data(last_adjustment_rec.receivables_trx_id);
674 
675  /*-------------------------------------------------+
676   | Fetch information on the previous posted        |
677   | transaction record for this BR. This information|
678   | is used to decide what processing is needed for |
679   | the Bills Receivable.                           |
680   +-------------------------------------------------*/
681   arp_br_housekeeper_pkg.prev_posted_trh(pg_BR_rec.transaction_history_id,
682                                          prev_trh_rec);
683 
684  /*--------------------------------------------------------------------+
685   | Check whether we have passed maturity date + risk_elimination_days |
686   | and branch the code accordingly                                    |
687   +--------------------------------------------------------------------*/
688 
689  /*--------------------------------------------------------+
690   | Check whether we have endorsed after the maturity date |
691   | and branch the code accordingly                        |
692   +--------------------------------------------------------*/
693   IF trunc(last_adjustment_rec.apply_date) >= trunc(pg_BR_rec.maturity_date) THEN
694 
695    /*--------------------------------------------------------------------+
696     | Check whether we have passed endorsed date + risk_elimination_days |
697     | and branch the code accordingly                                    |
698     +--------------------------------------------------------------------*/
699     IF trunc(pg_effective_date) < (trunc(last_adjustment_rec.apply_date) + NVL(pg_risk_elimination_days,0)) THEN
700 
701        /*----------------------------------------------------+
702         | BR was endorsed after maturity and endorsed date   |
703         | has not passed risk elimination days, do nothing   |
704         +----------------------------------------------------*/
705         write_debug_and_log('Bills Receivable was endorsed after maturity date and endorsement date ' ||
706                             'has not passed risk elimination days, Bills receivable not processed ');
707 
708     ELSE
709 
710      /*----------------------------------------------------------------+
711       | BR was endorsed after maturity and endorsement date has passed |
712       | risk elimination days. Approve the adjustment, deferred        |
713       | tax is moved as part of the adjustment. Deferred tax is only   |
714       | moved if tax to be moved exists.                               |
715       +----------------------------------------------------------------*/
716       IF pg_deferred_tax_exists THEN
717         l_move_deferred_tax := 'Y';
718       ELSE
719         l_move_deferred_tax := 'N';
720       END IF;
721 
722       IF prev_trh_rec.event = 'MATURITY_DATE' AND prev_trh_rec.postable_flag = 'Y' THEN
723 
724         l_move_deferred_tax := 'N';
725 
726       END IF;
727 
728      /*-------------------------------------+
729       | Approve the endorsement adjustment  |
730       +-------------------------------------*/
731       approve_Adjustment(last_adjustment_rec,l_move_deferred_tax);
732 
733     END IF; /* endorsement date past effective */
734 
735   ELSE
736 
740    /*--------------------------------------------------------------------+
737    /*---------------------------------+
738     | BR was endorsed before maturity |
739     +---------------------------------*/
741     | Check whether we have passed maturity date + risk_elimination_days |
742     | and branch the code accordingly                                    |
743     +--------------------------------------------------------------------*/
744     IF trunc(pg_effective_date) < (trunc(pg_BR_rec.maturity_date) + NVL(pg_risk_elimination_days,0)) THEN
745 
746      /*---------------------------------------------------------------------+
747       | Effective date has NOT passed maturity date + risk elimination days |
748       +---------------------------------------------------------------------*/
749 
750       IF trunc(pg_effective_date) < trunc(pg_BR_rec.maturity_date) THEN
751 
752        /*--------------------------------------------------------------+
753         | Effective date is earlier than the maturity date, do nothing |
754         +--------------------------------------------------------------*/
755         NULL;
756 
757       ELSE
758 
759        /*----------------------------------------------------------+
760         | Effective date is earlier than the maturity date + risk, |
761         | but later than maturity date. Move VAT if needed         |
762         +----------------------------------------------------------*/
763 
764         IF pg_deferred_tax_exists AND prev_trh_rec.event <> 'MATURITY_DATE' THEN
765 
766           create_maturity_date_event('Y',pg_BR_rec.maturity_date);
767 
768         END IF;
769 
770       END IF;
771     ELSE
772 
773      /*----------------------------------------------------------+
774       | BR was endorsed before maturity and effective date is    |
775       | later than the maturity date + risk                      |
776       +----------------------------------------------------------*/
777      /*-------------------------------------+
778       | Approve the endorsement adjustment  |
779       | Move VAT if needed                  |
780       +-------------------------------------*/
781 
782       IF pg_deferred_tax_exists AND prev_trh_rec.event <> 'MATURITY_DATE' THEN
783         l_move_deferred_tax := 'Y';
784       ELSE
785         l_move_deferred_tax := 'N';
786       END IF;
787 
788       approve_Adjustment(last_adjustment_rec,l_move_deferred_tax);
789 
790     END IF; /* effective date before maturity + risk */
791 
792   END IF; /* endorsed after maturity */
793 
794   write_debug_and_log( 'arp_br_housekeeper_pkg.process_endorsed()-' );
795 
796   EXCEPTION
797     WHEN OTHERS THEN
798       write_debug_and_log('Exception: arp_br_housekeeper_pkg.process_endorsed '||SQLERRM);
799       RAISE;
800 
801 END process_endorsed;
802 
803 
804 /*===========================================================================+
805  | PROCEDURE create_and_apply_Receipt                                        |
806  |    	                                                                     |
807  | DESCRIPTION                                                               |
808  |    Creates and applies a receipt to BR document on payment event. Moves   |
809  |    deferred tax if parameter p_move_deferred_tax is given as 'Y'.         |
810  |                                                                           |
811  | SCOPE - PUBLIC                                                            |
812  |                                                                           |
813  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
814  |    arp_util.debug                                                         |
815  |                                                                           |
816  | ARGUMENTS  : IN:  p_move_deferred_tax - Indicates whether deferred tax is |
817  |                                         moved.                            |
818  |                   p_receipt_date      - Date to be used for the receipt   |
819  |              OUT:                                                         |
820  |          IN/ OUT:                                                         |
821  |                                                                           |
822  | RETURNS    : NONE                                                         |
823  |                                                                           |
824  | MODIFICATION HISTORY                                                      |
825  |     17-APR-2000  Jani Rautiainen      Created                             |
826  |     30_APR-2001  V Crisostomo         Bug 1759305 : for rate types <> User|
827  |					 pass a null exchange rate	     |
828  |     25-MAY-2005  V Crisostomo	 SSA-R12 : add org_id                |
829  |                                                                           |
830  +===========================================================================*/
831 PROCEDURE create_and_apply_Receipt(p_move_deferred_tax         IN VARCHAR2 DEFAULT 'Y',
832                                    p_receipt_date              IN DATE) IS
833 
834  /*----------------------------------------+
835   | Cursor to fetch BR related information |
836   +----------------------------------------*/
837 
838   /*
839      Bug 1759305 : Receipt API expects an exchange rate ONLY when
840      exchange_rate_type = 'User', for all other exchange_rate_type values,
841      the exchange_rate should be null since the receipt API handles reading
842      the rate from the database
843   */
844 
848          decode(ps.exchange_rate_type,'User',ps.exchange_rate,null) exchange_rate,
845   CURSOR BR_cur IS
846   SELECT ps.invoice_currency_code,
847          ps.exchange_rate_type,
849          ps.exchange_date,
850          ps.customer_id,
851          ps.customer_trx_id,
852          ps.payment_schedule_id,
853          ps.amount_due_remaining,
854          ct.drawee_site_use_id,
855          ct.override_remit_account_flag,
856          ct.remit_bank_acct_use_id,
857          ct.customer_bank_account_id,
858          ct.trx_number,
859          ct.term_due_date maturity_date,
860          ct.org_id
861   FROM ra_customer_trx ct, ar_payment_schedules ps
862   WHERE ct.customer_trx_id = pg_BR_rec.customer_trx_id
863   AND   ps.customer_trx_id = ct.customer_trx_id;
864 
865   l_return_status            VARCHAR2(1);
866   l_msg_count                NUMBER;
867   l_msg_data                 VARCHAR2(2000);
868   l_cr_id                    NUMBER;
869   l_receipt_number           ar_cash_receipts.receipt_number%TYPE;
870   l_receipt_date             DATE;
871   BR_rec                     BR_cur%ROWTYPE;
872   l_trh_rec                  ar_transaction_history%ROWTYPE;
873   l_transaction_history_id   ar_transaction_history.transaction_history_id%TYPE;
874   l_default_gl_date          DATE;
875   l_org_return_status        VARCHAR2(1);
876   l_org_id                   NUMBER;
877 
878 BEGIN
879   write_debug_and_log( 'arp_br_housekeeper_pkg.create_and_apply_Receipt()+' );
880 
881 
882   BEGIN
883 
884   /*------------------------------+
885    | Fetch BR related information |
886    +------------------------------*/
887    OPEN BR_cur;
888    FETCH BR_cur INTO BR_rec;
889 
890   /*------------------------------------------------------------+
891    | If BR is not found, stop processing and raise an exception |
892    +------------------------------------------------------------*/
893    IF BR_cur%NOTFOUND THEN
894 
895      write_debug_and_log( 'Bills Receivable transaction cannot be found' );
896      CLOSE BR_cur;
897      APP_EXCEPTION.raise_exception;
898 
899    END IF;
900 
901    CLOSE BR_cur;
902 
903    /* SSA change */
904    l_org_id := BR_Rec.org_id;
905    l_org_return_status := FND_API.G_RET_STS_SUCCESS;
906    ar_mo_cache_utils.set_org_context_in_api(p_org_id =>l_org_id,
907                                             p_return_status =>l_org_return_status);
908 
909    IF l_org_return_status <> FND_API.G_RET_STS_SUCCESS THEN
910       write_debug_and_log('arp_br_housekeeper_pkg.create_and_apply_Receipt : l_org_return_status <> SUCCESS');
911       RAISE API_exception;
912    ELSE
913 
914   /*-------------------------------------------+
915    | Check if receipt number inherited from BR |
916    | If not inherited, the Receipt API will    |
917    | default it from sequence                  |
918    +-------------------------------------------*/
919    IF NVL(pg_rct_inherit_inv_num_flag,'N') = 'Y' THEN
920      write_debug_and_log( 'pg_rct_inherit_inv_num_flag = Y ' );
921 
922      l_receipt_number := BR_rec.trx_number;
923 
924      write_debug_and_log( 'l_receipt_number = '||l_receipt_number );
925 
926    END IF;
927 
928    l_default_gl_date := arp_br_housekeeper_pkg.validate_against_doc_gl_date(pg_gl_date,
929                                                                             pg_BR_rec.gl_date);
930 
931   /*--------------------------------------------------------+
932    | Receipt date, apply date, deposit date and receipt     |
933    | maturity date are BR maturity_date if the BR was       |
934    | remitted before maturity. If the BR was remitted after |
935    | maturity date then the remittance batch date +         |
936    | collection days is used.                               |
937    +--------------------------------------------------------*/
938    l_receipt_date := p_receipt_date;
939 
940    write_debug_and_log( 'l_receipt_date = '||to_char(l_receipt_date));
941 
942 
943   /*------------------------------------------------+
944    | Call Receipt API to create and apply a receipt |
945    +------------------------------------------------*/
946    AR_RECEIPT_API_PUB.Create_and_apply(
947       p_api_version                  => 1.0,
948       p_init_msg_list                => FND_API.G_TRUE,
949       x_return_status                => l_return_status,
950       x_msg_count                    => l_msg_count,
951       x_msg_data                     => l_msg_data,
952       p_currency_code                => BR_rec.invoice_currency_code,
953       p_exchange_rate_type           => BR_rec.exchange_rate_type,
954       p_exchange_rate                => BR_rec.exchange_rate,
955       p_exchange_rate_date           => BR_rec.exchange_date,
956       p_amount                       => BR_rec.amount_due_remaining,
957       p_receipt_number               => l_receipt_number,
958       p_receipt_date                 => l_receipt_date,
959       p_gl_date                      => l_default_gl_date,
960       p_maturity_date                => l_receipt_date,
961       p_called_from                  => pg_called_from,
962       p_customer_id                  => BR_rec.customer_id,
963       p_customer_bank_account_id     => BR_rec.customer_bank_account_id,
964       p_customer_site_use_id         => BR_rec.drawee_site_use_id,
965       p_override_remit_account_flag  => BR_rec.override_remit_account_flag,
969       p_cr_id		             => l_cr_id,
966       p_remittance_bank_account_id   => pg_remit_bank_acct_use_id,
967       p_deposit_date                 => l_receipt_date,
968       p_receipt_method_id            => pg_receipt_method_id,
970       p_customer_trx_id              => BR_rec.customer_trx_id,
971       p_applied_payment_schedule_id  => BR_rec.payment_schedule_id,
972       p_amount_applied               => BR_rec.amount_due_remaining,
973       p_apply_date                   => l_receipt_date,
974       p_apply_gl_date                => l_default_gl_date,
975       p_move_deferred_tax            => p_move_deferred_tax,
976       p_org_id                       => BR_rec.org_id);
977 
978  /*------------------------------------------------+
979   | Write API output to the concurrent program log |
980   +------------------------------------------------*/
981   IF NVL(l_msg_count,0)  > 0 Then
982 
983       /* Bug 1855821 : indicate in the log file the receipt API procedure that raised the error */
984       write_debug_and_log('API error count : AR_RECEIPT_API_PUB.Create_and_apply : '||to_char(NVL(l_msg_count,0)));
985 
986       write_API_output(l_msg_count,l_msg_data);
987 
988   END IF;
989 
990  /*-----------------------------------------------------+
991   | If API return status is not SUCCESS raise exception |
992   +-----------------------------------------------------*/
993   IF l_return_status = FND_API.G_RET_STS_SUCCESS Then
994 
995    /*-----------------------------------------------------+
996     | Success update the batch id on the current cash     |
997     | receipt history record.                             |
998     +-----------------------------------------------------*/
999     arp_br_remit_batches.update_br_remit_batch_to_crh(l_cr_id,pg_BR_rec.reserved_value);
1000 
1001   ELSE
1002    /*---------------------------+
1003     | Error, raise an exception |
1004     +---------------------------*/
1005     RAISE API_exception;
1006 
1007   END IF;
1008   END IF; /* l_org_return_status <> FND_API.G_RET_STS_SUCCESS */
1009 
1010  /*----------------------------------+
1011   | APIs propagate exception upwards |
1012   +----------------------------------*/
1013   EXCEPTION
1014     WHEN API_exception THEN
1015       write_debug_and_log('API Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt '||SQLERRM);
1016       RAISE;
1017 
1018     WHEN OTHERS THEN
1019       write_debug_and_log('Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt '||SQLERRM);
1020       RAISE;
1021 
1022   END;
1023 
1024  /*-----------------------------------------------------------------+
1025   |  Payment schedule was closed, create transaction history record |
1026   +-----------------------------------------------------------------*/
1027 
1028  /*--------------------------------------------+
1029   |  Initialize the transaction history record |
1030   +--------------------------------------------*/
1031   IF l_org_return_status = FND_API.G_RET_STS_SUCCESS THEN
1032   l_trh_rec.customer_trx_id          := pg_BR_rec.customer_trx_id;
1033   l_trh_rec.status                   := 'CLOSED';
1034   l_trh_rec.event                    := 'CLOSED';
1035   l_trh_rec.batch_id                 := NULL;
1036   l_trh_rec.trx_date                 := l_receipt_date;
1037   l_trh_rec.gl_date                  := l_default_gl_date;
1038   l_trh_rec.current_record_flag      := 'Y';
1039   l_trh_rec.current_accounted_flag   := 'N';
1040   l_trh_rec.postable_flag            := 'N';
1041   l_trh_rec.first_posted_record_flag := 'N';
1042   l_trh_rec.posting_control_id       := -3;
1043   l_trh_rec.gl_posted_date           := NULL;
1044   l_trh_rec.prv_trx_history_id       := NULL;
1045   l_trh_rec.created_from             := 'ARRBRHKB';
1046   l_trh_rec.comments                 := NULL;
1047   l_trh_rec.maturity_date            := pg_BR_rec.maturity_date;
1048   l_trh_rec.org_id                   := pg_BR_rec.org_id;
1049 
1050  /*----------------------------------------+
1051   |  Insert the transaction history record |
1052   +----------------------------------------*/
1053   ARP_PROC_TRANSACTION_HISTORY.insert_transaction_history(l_trh_rec,
1054                                                           l_transaction_history_id);
1055 
1056   END IF; /* l_org_return_status <> FND_API.G_RET_STS_SUCCESS */
1057 
1058   write_debug_and_log( 'arp_br_housekeeper_pkg.create_and_apply_Receipt()-' );
1059 
1060   EXCEPTION
1061     WHEN OTHERS THEN
1062       write_debug_and_log('Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt'||SQLERRM);
1063       RAISE;
1064 
1065 END create_and_apply_Receipt;
1066 
1067 /*===========================================================================+
1068  | PROCEDURE approve_Adjustment                                              |
1069  |    	                                                                     |
1070  | DESCRIPTION                                                               |
1071  |    Approves adjusment (endorsement) related to BR document on risk        |
1072  |    elimination event. Moves deferred tax if parameter p_move_deferred_tax |
1073  |    is given as 'Y'.                                                       |
1074  |                                                                           |
1075  | SCOPE - PUBLIC                                                            |
1076  |                                                                           |
1077  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1078  |    arp_util.debug                                                         |
1082  |              OUT:                                                         |
1079  |                                                                           |
1080  | ARGUMENTS  : IN:  p_move_deferred_tax - Indicates whether deferred tax is |
1081  |                                         moved.                            |
1083  |          IN/ OUT:                                                         |
1084  |                                                                           |
1085  | RETURNS    : NONE                                                         |
1086  |                                                                           |
1087  | MODIFICATION HISTORY                                                      |
1088  |     17-APR-2000  Jani Rautiainen      Created                             |
1089  |                                                                           |
1090  +===========================================================================*/
1091 PROCEDURE approve_Adjustment(p_adjustment_rec    IN OUT NOCOPY ar_adjustments%ROWTYPE,
1092                              p_move_deferred_tax IN     VARCHAR2 DEFAULT 'Y') IS
1093 
1094   l_adj_rec            ar_adjustments%rowtype;
1095   l_return_status      VARCHAR2(1);
1096   l_msg_count          NUMBER;
1097   l_msg_data           VARCHAR2(2000);
1098 
1099   l_trh_rec                  ar_transaction_history%ROWTYPE;
1100   l_transaction_history_id   ar_transaction_history.transaction_history_id%TYPE;
1101   l_default_gl_date          DATE;
1102   l_event_date               DATE;
1103 
1104   l_org_return_status        VARCHAR2(1);
1105   l_org_id                   NUMBER;
1106 BEGIN
1107   write_debug_and_log( 'arp_br_housekeeper_pkg.approve_Adjustment()+' );
1108 
1109   /* SSA change */
1110   l_org_id := p_adjustment_rec.org_id;
1111   l_org_return_status := FND_API.G_RET_STS_SUCCESS;
1112   ar_mo_cache_utils.set_org_context_in_api(p_org_id =>l_org_id,
1113                                            p_return_status =>l_org_return_status);
1114 
1115   IF l_org_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1116      write_debug_and_log('arp_br_housekeeper_pkg.approve_adjustment : l_org_return_status <> SUCCESS');
1117      RAISE API_exception;
1118   ELSE
1119 
1120  /*--------------------------------------------------------+
1121   | Check whether we have endorsed after the maturity date |
1122   | and set the event data accordingly                     |
1123   +--------------------------------------------------------*/
1124   IF trunc(p_adjustment_rec.apply_date) >= trunc(pg_BR_rec.maturity_date) THEN
1125 
1126     l_event_date                := p_adjustment_rec.apply_date + NVL(pg_risk_elimination_days,0);
1127     p_adjustment_rec.apply_date := p_adjustment_rec.apply_date + NVL(pg_risk_elimination_days,0);
1128 
1129   ELSE
1130 
1131     l_event_date                := pg_BR_rec.maturity_date + NVL(pg_risk_elimination_days,0);
1132     p_adjustment_rec.apply_date := pg_BR_rec.maturity_date;
1133 
1134   END IF;
1135 
1136  /*----------------------------------------------+
1137   | Check that the GL date on the adjustment is  |
1138   | still valid. If it is not then try to default|
1139   | the gl date given to the housekeeper by the  |
1140   | user. If that is also invalid default to the |
1141   | next available open period.                  |
1142   +----------------------------------------------*/
1143   l_default_gl_date := arp_br_housekeeper_pkg.validate_and_default_gl_date(p_adjustment_rec.gl_date,
1144                                                                            NULL,NULL,NULL,NULL,
1145                                                                            pg_gl_date,
1146                                                                            NULL,NULL);
1147 
1148  /*----------------------------------------------+
1149   | The GL date might be updated give the        |
1150   | adjustment record as parameter to the API    |
1151   +----------------------------------------------*/
1152   IF l_default_gl_date IS NOT NULL THEN
1153 
1154     l_adj_rec         := p_adjustment_rec;
1155     l_adj_rec.status  := 'A';
1156     l_adj_rec.gl_date := l_default_gl_date;
1157 
1158   END IF;
1159 
1160   BEGIN
1161    /*----------------------------------------------+
1162     | Call Adjustment API to approve an adjustment |
1163     +----------------------------------------------*/
1164     ar_adjust_pub.approve_Adjustment (
1165       p_api_name          => 'AR_ADJUST_PUB',
1166       p_api_version       => 1.0,
1167       p_init_msg_list     => FND_API.G_TRUE,
1168       p_msg_count         => l_msg_count,
1169       p_msg_data          => l_msg_data,
1170       p_return_status     => l_return_status,
1171       p_adj_rec             => l_adj_rec,
1172       p_chk_approval_limits => FND_API.G_FALSE,
1173       p_move_deferred_tax   => p_move_deferred_tax,
1174       p_old_adjust_id       => p_adjustment_rec.adjustment_id,
1175       p_org_id              => p_adjustment_rec.org_id);
1176 
1177    /*------------------------------------------------+
1178     | Write API output to the concurrent program log |
1179     +------------------------------------------------*/
1180     IF NVL(l_msg_count,0)  > 0 Then
1181 
1182         /* Bug 1855821 :
1183            the errors raised here are from Adjustment API, but since this is similar to the
1184            Receipt API call, I am applying the same code changes done for Receipt API where
1185            I am printing more information in the log file */
1186         write_debug_and_log('API error count : AR_ADJUST_PUB.approve_adjustment : '||to_char(NVL(l_msg_count,0)));
1190     END IF;
1187 
1188         write_API_output(l_msg_count,l_msg_data);
1189 
1191 
1192  /*-----------------------------------------------------+
1193   | If API return status is not SUCCESS raise exception |
1194   +-----------------------------------------------------*/
1195   IF l_return_status = FND_API.G_RET_STS_SUCCESS Then
1196 
1197    /*-----------------------------------------------------+
1198     | Success do nothing, else branch introduced to make  |
1199     | sure that NULL case will also raise exception       |
1200     +-----------------------------------------------------*/
1201     NULL;
1202 
1203   ELSE
1204    /*---------------------------+
1205     | Error, raise an exception |
1206     +---------------------------*/
1207     RAISE API_exception;
1208 
1209   END IF;
1210 
1211  /*----------------------------------+
1212   | APIs propagate exception upwards |
1213   +----------------------------------*/
1214     EXCEPTION
1215       WHEN API_exception THEN
1216         write_debug_and_log('API Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt '||SQLERRM);
1217         RAISE;
1218 
1219       WHEN OTHERS THEN
1220         write_debug_and_log('Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt '||SQLERRM);
1221         RAISE;
1222 
1223   END;
1224 
1225  /*-----------------------------------------------------------------+
1226   |  Payment schedule was closed, create transaction history record |
1227   +-----------------------------------------------------------------*/
1228 
1229  /*--------------------------------------------+
1230   |  Initialize the transaction history record |
1231   +--------------------------------------------*/
1232   l_trh_rec.customer_trx_id          := pg_BR_rec.customer_trx_id;
1233   l_trh_rec.status                   := 'CLOSED';
1234   l_trh_rec.event                    := 'RISK_ELIMINATED';
1235   l_trh_rec.batch_id                 := NULL;
1236   l_trh_rec.trx_date                 := l_event_date;
1237   l_trh_rec.gl_date                  := l_adj_rec.gl_date;
1238   l_trh_rec.current_record_flag      := 'Y';
1239   l_trh_rec.current_accounted_flag   := 'N';
1240   l_trh_rec.postable_flag            := 'N';
1241   l_trh_rec.first_posted_record_flag := 'N';
1242   l_trh_rec.posting_control_id       := -3;
1243   l_trh_rec.gl_posted_date           := NULL;
1244   l_trh_rec.prv_trx_history_id       := NULL;
1245   l_trh_rec.created_from             := 'ARRBRHKB';
1246   l_trh_rec.comments                 := NULL;
1247   l_trh_rec.maturity_date            := pg_BR_rec.maturity_date;
1248   l_trh_rec.org_id                   := pg_BR_rec.org_id;
1249 
1250  /*----------------------------------------+
1251   |  Insert the transaction history record |
1252   +----------------------------------------*/
1253   ARP_PROC_TRANSACTION_HISTORY.insert_transaction_history(l_trh_rec,
1254                                                           l_transaction_history_id);
1255 
1256   END IF;  /* l_org_return_status <> FND_API.G_RET_STS_SUCCESS */
1257 
1258   write_debug_and_log( 'arp_br_housekeeper_pkg.approve_Adjustment()-' );
1259 
1260   EXCEPTION
1261     WHEN OTHERS THEN
1262       write_debug_and_log('Exception: arp_br_housekeeper_pkg.approve_Adjustment'||SQLERRM);
1263       RAISE;
1264 
1265 END approve_Adjustment;
1266 
1267 /*===========================================================================+
1268  | PROCEDURE apply_Receipt                                                   |
1269  |    	                                                                     |
1270  | DESCRIPTION                                                               |
1271  |    Unapplies BR document from Short Term Debt and creates normal          |
1272  |    application on risk elimination event. Moves deferred tax if parameter |
1273  |    p_move_deferred_tax is given as 'Y'.                                   |
1274  |                                                                           |
1275  | SCOPE - PUBLIC                                                            |
1276  |                                                                           |
1277  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1278  |    arp_util.debug                                                         |
1279  |                                                                           |
1280  | ARGUMENTS  : IN:  p_move_deferred_tax - Indicates whether deferred tax is |
1281  |                                         moved.                            |
1282  |              OUT:                                                         |
1283  |          IN/ OUT:                                                         |
1284  |                                                                           |
1285  | RETURNS    : NONE                                                         |
1286  |                                                                           |
1287  | MODIFICATION HISTORY                                                      |
1288  |     17-APR-2000  Jani Rautiainen      Created                             |
1289  |                                                                           |
1290  +===========================================================================*/
1291 PROCEDURE apply_Receipt(p_move_deferred_tax         VARCHAR2 DEFAULT 'Y',
1292                         p_receipt_date              IN DATE) IS
1293 
1294  /*--------------------------------------------------+
1295   | Cursor to fetch last Short Term Debt application |
1296   +--------------------------------------------------*/
1300     from ar_receivable_applications rap
1297   CURSOR last_std_application_cur IS
1298     select rap.receivable_application_id, rap.cash_receipt_id, rap.gl_date, rap.apply_date,
1299            rap.org_id
1301     where rap.link_to_customer_trx_id     = pg_BR_rec.customer_trx_id
1302     and   rap.status                      = 'ACTIVITY'
1303     and   rap.applied_payment_schedule_id = -2
1304     and   rap.display                     = 'Y'
1305     order by rap.receivable_application_id desc;
1306 
1307   l_return_status  VARCHAR2(1);
1308   l_msg_count      NUMBER;
1309   l_msg_data       VARCHAR2(2000);
1310   l_apply_date     DATE;
1311 
1312   last_std_application_rec   last_std_application_cur%ROWTYPE;
1313   l_trh_rec                  ar_transaction_history%ROWTYPE;
1314   l_transaction_history_id   ar_transaction_history.transaction_history_id%TYPE;
1315   l_default_gl_date          DATE;
1316   l_event_date               DATE;
1317 
1318   l_org_return_status        VARCHAR2(1);
1319   l_org_id                   NUMBER;
1320 BEGIN
1321   write_debug_and_log( 'arp_br_housekeeper_pkg.apply_Receipt()+' );
1322 
1323  /*------------------------+
1324   | Fetch last application |
1325   +------------------------*/
1326   OPEN last_std_application_cur;
1327   FETCH last_std_application_cur INTO last_std_application_rec;
1328 
1329  /*------------------------------------------------------------------+
1330   | If last STD is not found, stop processing and raise an exception |
1331   +------------------------------------------------------------------*/
1332   IF last_std_application_cur%NOTFOUND THEN
1333 
1334      write_debug_and_log( 'Last Short Term Debt application cannot be found' );
1335      CLOSE last_std_application_cur;
1336      APP_EXCEPTION.raise_exception;
1337 
1338    END IF;
1339 
1340   CLOSE last_std_application_cur;
1341 
1342   /* SSA change */
1343   l_org_id := last_std_application_rec.org_id;
1344   l_org_return_status := FND_API.G_RET_STS_SUCCESS;
1345   ar_mo_cache_utils.set_org_context_in_api(p_org_id =>l_org_id,
1346                                            p_return_status =>l_org_return_status);
1347 
1348   IF l_org_return_status <> FND_API.G_RET_STS_SUCCESS THEN
1349      write_debug_and_log('arp_br_housekeeper_pkg.apply_receipt : l_org_return_status <> SUCCESS');
1350      RAISE API_exception;
1351   ELSE
1352 
1353   l_default_gl_date := arp_br_housekeeper_pkg.validate_against_doc_gl_date(pg_gl_date,
1354                                                                            last_std_application_rec.gl_date);
1355   BEGIN
1356    /*------------------------------------+
1357     | Unapply from STD using Receipt API |
1358     +------------------------------------*/
1359 
1360     AR_RECEIPT_API_PUB.Activity_unapplication(
1361       p_api_version                 => 1.0,
1362       p_init_msg_list               => FND_API.G_TRUE,
1363       x_return_status               => l_return_status,
1364       x_msg_count                   => l_msg_count,
1365       x_msg_data                    => l_msg_data,
1366       p_cash_receipt_id             => last_std_application_rec.cash_receipt_id,
1367       p_receivable_application_id   => last_std_application_rec.receivable_application_id,
1368       p_reversal_gl_date            => l_default_gl_date,
1369       p_called_from                 => pg_called_from,
1370       p_org_id                      => last_std_application_rec.org_id);
1371 
1372    /*------------------------------------------------+
1373     | Write API output to the concurrent program log |
1374     +------------------------------------------------*/
1375     IF NVL(l_msg_count,0)  > 0 Then
1376 
1377         /* Bug 1855821 : indicate in the log file the receipt API procedure that raised the error */
1378         write_debug_and_log('API error count : AR_RECEIPT_API_PUB.Activity_unapplication : '||
1379                              to_char(NVL(l_msg_count,0)));
1380         write_API_output(l_msg_count,l_msg_data);
1381 
1382     END IF;
1383 
1384    /*-----------------------------------------------------+
1385     | If API return status is not SUCCESS raise exception |
1386     +-----------------------------------------------------*/
1387     IF l_return_status = FND_API.G_RET_STS_SUCCESS Then
1388 
1389      /*-----------------------------------------------------+
1390       | Success do nothing, else branch introduced to make  |
1391       | sure that NULL case will also raise exception       |
1392       +-----------------------------------------------------*/
1393       NULL;
1394 
1395     ELSE
1396      /*---------------------------+
1397       | Error, raise an exception |
1398       +---------------------------*/
1399       RAISE API_exception;
1400 
1401     END IF;
1402 
1403    /*----------------------------------+
1404     | APIs propagate exception upwards |
1405     +----------------------------------*/
1406     EXCEPTION
1407       WHEN API_exception THEN
1408         write_debug_and_log('API Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt '||SQLERRM);
1409         RAISE;
1410 
1411       WHEN OTHERS THEN
1412         write_debug_and_log('Exception: arp_br_housekeeper_pkg.apply_Receipt '||SQLERRM);
1413         RAISE;
1414   END;
1415 
1416   BEGIN
1417 
1418   /*-----------------------------------------------------+
1419    | Apply date is maturity_date + risk elimination days |
1420    +-----------------------------------------------------*/
1421    l_apply_date := p_receipt_date;
1422 
1426 
1423    IF trunc(last_std_application_rec.apply_date) > trunc(l_apply_date) THEN
1424 
1425      l_apply_date := last_std_application_rec.apply_date;
1427    END IF;
1428 
1429    /*---------------------------------------------+
1430     | Create normal application using Receipt API |
1431     +---------------------------------------------*/
1432 
1433     write_debug_and_log('will call AR_RECEIPT_API_PUB.Apply');
1434 
1435     AR_RECEIPT_API_PUB.Apply(
1436       p_api_version                 => 1.0,
1437       p_init_msg_list               => FND_API.G_TRUE,
1438       x_return_status               => l_return_status,
1439       x_msg_count                   => l_msg_count,
1440       x_msg_data                    => l_msg_data,
1441       p_cash_receipt_id             => last_std_application_rec.cash_receipt_id,
1442       p_customer_trx_id             => pg_BR_rec.customer_trx_id,
1443       p_applied_payment_schedule_id => pg_BR_rec.payment_schedule_id,
1444       p_amount_applied              => pg_BR_rec.amount_due_remaining,
1445       p_apply_date                  => l_apply_date,
1446       p_apply_gl_date               => l_default_gl_date,
1447       p_called_from                 => pg_called_from,
1448       p_move_deferred_tax           => p_move_deferred_tax,
1449       p_org_id                      => pg_BR_rec.org_id);
1450 
1451    /*------------------------------------------------+
1452     | Write API output to the concurrent program log |
1453     +------------------------------------------------*/
1454     IF NVL(l_msg_count,0)  > 0 Then
1455 
1456         /* Bug 1855821 : indicate in the log file the receipt API procedure that raised the error */
1457         write_debug_and_log('API error count : AR_RECEIPT_API_PUB.Apply : '|| to_char(NVL(l_msg_count,0)));
1458 
1459         write_API_output(l_msg_count,l_msg_data);
1460 
1461     END IF;
1462 
1463    /*-----------------------------------------------------+
1464     | If API return status is not SUCCESS raise exception |
1465     +-----------------------------------------------------*/
1466     IF l_return_status = FND_API.G_RET_STS_SUCCESS Then
1467 
1468      /*-----------------------------------------------------+
1469       | Success do nothing, else branch introduced to make  |
1470       | sure that NULL case will also raise exception       |
1471       +-----------------------------------------------------*/
1472       NULL;
1473 
1474     ELSE
1475      /*---------------------------+
1476       | Error, raise an exception |
1477       +---------------------------*/
1478       RAISE API_exception;
1479 
1480     END IF;
1481 
1482 
1483 
1484    /*----------------------------------+
1485     | APIs propagate exception upwards |
1486     +----------------------------------*/
1487     EXCEPTION
1488       WHEN API_exception THEN
1489         write_debug_and_log('API Exception: arp_br_housekeeper_pkg.create_and_apply_Receipt '||SQLERRM);
1490         RAISE;
1491 
1492       WHEN OTHERS THEN
1493         write_debug_and_log('Exception: arp_br_housekeeper_pkg.apply_Receipt '||SQLERRM);
1494         RAISE;
1495   END;
1496 
1497  /*-----------------------------------------------------------------+
1498   |  Payment schedule was closed, create transaction history record |
1499   +-----------------------------------------------------------------*/
1500 
1501  /*--------------------------------------------------------+
1502   | Check whether we have remitted after the maturity date |
1503   | and set the event data accordingly                     |
1504   +--------------------------------------------------------*/
1505   IF trunc(pg_remittance_batch_date) >= trunc(pg_BR_rec.maturity_date) THEN
1506     l_event_date    := pg_remittance_batch_date + NVL(pg_risk_elimination_days,0);
1507   ELSE
1508     l_event_date    := pg_BR_rec.maturity_date  + NVL(pg_risk_elimination_days,0);
1509   END IF;
1510 
1511  /*--------------------------------------------+
1512   |  Initialize the transaction history record |
1513   +--------------------------------------------*/
1514   l_trh_rec.customer_trx_id          := pg_BR_rec.customer_trx_id;
1515   l_trh_rec.status                   := 'CLOSED';
1516   l_trh_rec.event                    := 'RISK_ELIMINATED';
1517   l_trh_rec.batch_id                 := NULL;
1518   l_trh_rec.trx_date                 := l_event_date;
1519   l_trh_rec.gl_date                  := pg_gl_date;
1520   l_trh_rec.current_record_flag      := 'Y';
1521   l_trh_rec.current_accounted_flag   := 'N';
1522   l_trh_rec.postable_flag            := 'N';
1523   l_trh_rec.first_posted_record_flag := 'N';
1524   l_trh_rec.posting_control_id       := -3;
1525   l_trh_rec.gl_posted_date           := NULL;
1526   l_trh_rec.prv_trx_history_id       := NULL;
1527   l_trh_rec.created_from             := 'ARRBRHKB';
1528   l_trh_rec.comments                 := NULL;
1529   l_trh_rec.maturity_date            := pg_BR_rec.maturity_date;
1530   l_trh_rec.org_id                   := pg_BR_rec.org_id;
1531 
1532  /*----------------------------------------+
1533   |  Insert the transaction history record |
1534   +----------------------------------------*/
1535   ARP_PROC_TRANSACTION_HISTORY.insert_transaction_history(l_trh_rec,
1536                                                           l_transaction_history_id);
1537 
1538 
1539   END IF;  /* l_org_return_status <> FND_API.G_RET_STS_SUCCESS */
1540 
1541   write_debug_and_log( 'arp_br_housekeeper_pkg.apply_Receipt()-' );
1542 
1543   EXCEPTION
1544     WHEN OTHERS THEN
1548 END apply_Receipt;
1545       write_debug_and_log('Exception: arp_br_housekeeper_pkg.apply_Receipt '||SQLERRM);
1546       RAISE;
1547 
1549 
1550 /*===========================================================================+
1551  | PROCEDURE create_maturity_date_event                                      |
1552  |    	                                                                     |
1553  | DESCRIPTION                                                               |
1554  |    Create maturity date event in transaction history table.               |
1555  |    Moves deferred tax if parameter p_move_deferred_tax is given as 'Y'.   |
1556  |                                                                           |
1557  | SCOPE - PUBLIC                                                            |
1558  |                                                                           |
1559  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1560  |    arp_util.debug                                                         |
1561  |                                                                           |
1562  | ARGUMENTS  : IN:  p_move_deferred_tax - Indicates whether deferred tax is |
1563  |                                         moved.                            |
1564  |                   p_event_date        - The date that the event occurs    |
1565  |              OUT:                                                         |
1566  |          IN/ OUT:                                                         |
1567  |                                                                           |
1568  | RETURNS    : NONE                                                         |
1569  |                                                                           |
1570  | MODIFICATION HISTORY                                                      |
1571  |     17-APR-2000  Jani Rautiainen      Created                             |
1572  |                                                                           |
1573  +===========================================================================*/
1574 PROCEDURE create_maturity_date_event(p_move_deferred_tax VARCHAR2 DEFAULT 'Y',
1575                                      p_event_date        DATE) IS
1576 
1577   l_trh_rec                ar_transaction_history%ROWTYPE;
1578   l_transaction_history_id ar_transaction_history.transaction_history_id%TYPE;
1579   l_event_date             DATE;
1580 BEGIN
1581   write_debug_and_log( 'arp_br_housekeeper_pkg.create_maturity_date_event()+' );
1582 
1583  /*-----------------------+
1584   | fetch previous record |
1585   +-----------------------*/
1586   l_trh_rec.customer_trx_id := pg_BR_rec.customer_trx_id;
1587 
1588   ARP_TRANSACTION_HISTORY_PKG.fetch_f_trx_id(l_trh_rec);
1589 
1590  /*--------------------------------------------------------+
1591   | Check whether we have remitted after the maturity date |
1592   | and set the event data accordingly                     |
1593   +--------------------------------------------------------*/
1594   IF l_trh_rec.status = 'ENDORSED' THEN
1595       l_event_date    := pg_BR_rec.maturity_date;
1596   ELSE
1597     IF trunc(pg_remittance_batch_date) >= trunc(pg_BR_rec.maturity_date) THEN
1598       l_event_date    := pg_remittance_batch_date;
1599     ELSE
1600       l_event_date    := pg_BR_rec.maturity_date;
1601     END IF;
1602   END IF;
1603 
1604  /*----------------------------------------+
1605   | Fill in information for the new record |
1606   +----------------------------------------*/
1607   l_trh_rec.transaction_history_id   := NULL;
1608   l_trh_rec.event                    := 'MATURITY_DATE';
1609   l_trh_rec.batch_id                 := NULL;
1610   l_trh_rec.trx_date                 := l_event_date;
1611   l_trh_rec.gl_date                  := pg_BR_rec.maturity_date;
1612   l_trh_rec.current_record_flag      := 'Y';
1613   l_trh_rec.first_posted_record_flag := 'N';
1614   l_trh_rec.posting_control_id       := -3;
1615   l_trh_rec.gl_posted_date           := NULL;
1616   l_trh_rec.prv_trx_history_id       := NULL;
1617   l_trh_rec.created_from             := 'ARRBRHKB';
1618   l_trh_rec.comments                 := NULL;
1619   l_trh_rec.maturity_date            := pg_BR_rec.maturity_date;
1620   l_trh_rec.org_id                   := pg_BR_rec.org_id;
1621 
1622  /*--------------------------------------------+
1623   | The status changes for maturity date event |
1624   | only for BRs factored with recource        |
1625   +--------------------------------------------*/
1626   IF l_trh_rec.status = 'FACTORED' THEN
1627     l_trh_rec.status := 'MATURED_PEND_RISK_ELIMINATION';
1628   END IF;
1629 
1630  /*---------------------------------------------+
1631   | Maturity date event has only deferred tax   |
1632   | accounting under it. So if tax is not moved |
1633   | the record is not postable.                 |
1634   +---------------------------------------------*/
1635   IF p_move_deferred_tax = 'Y' THEN
1636     l_trh_rec.postable_flag            := 'Y';
1637     l_trh_rec.current_accounted_flag   := 'Y';
1638   ELSE
1639     l_trh_rec.postable_flag            := 'N';
1640     l_trh_rec.current_accounted_flag   := 'N';
1641   END IF;
1642 
1643  /*--------------------------------------------------+
1644   | Call TRH entity handler with event MATURITY_DATE |
1645   +--------------------------------------------------*/
1646   ARP_PROC_TRANSACTION_HISTORY.insert_transaction_history(l_trh_rec,
1647                                                           l_transaction_history_id,
1648                                                           p_move_deferred_tax);
1649 
1653     WHEN OTHERS THEN
1650   write_debug_and_log( 'arp_br_housekeeper_pkg.create_maturity_date_event()-' );
1651 
1652   EXCEPTION
1654       write_debug_and_log('Exception: arp_br_housekeeper_pkg.create_maturity_date_event '||SQLERRM);
1655       RAISE;
1656 
1657 END create_maturity_date_event;
1658 
1659 /*===========================================================================+
1660  | PROCEDURE prev_posted_trh                                                 |
1661  |    	                                                                     |
1662  | DESCRIPTION                                                               |
1663  |    This function fetches the previous posted transaction history record   |
1664  |                                                                           |
1665  | SCOPE - PUBLIC                                                            |
1666  |                                                                           |
1667  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1668  |    arp_util.debug                                                         |
1669  |                                                                           |
1670  | ARGUMENTS  : IN                                                           |
1671  |               p_transaction_history_id - BR transaction history_id        |
1672  |                                                                           |
1673  |              OUT                                                          |
1674  |               p_trh_rec - BR transaction history record                   |
1675  |                                                                           |
1676  |                                                                           |
1677  | MODIFICATION HISTORY                                                      |
1678  |     30-JUN-2000  Jani Rautiainen      Created                             |
1679  |                                                                           |
1680  +===========================================================================*/
1681 PROCEDURE prev_posted_trh(p_transaction_history_id IN  ar_transaction_history.transaction_history_id%TYPE,
1682                           p_trh_rec                OUT NOCOPY ar_transaction_history%ROWTYPE) IS
1683 
1684  /*------------------------------------------------------------+
1685   | Cursor to fetch previous posted transaction history record |
1686   +------------------------------------------------------------*/
1687   CURSOR prev_trh_cur IS
1688     select th.*
1689     from ar_transaction_history th
1690     where (postable_flag = 'Y' or event = 'MATURITY_DATE')
1691     connect by prior prv_trx_history_id = transaction_history_id
1692     start with transaction_history_id = p_transaction_history_id
1693     order by transaction_history_id desc;
1694 
1695 BEGIN
1696   write_debug_and_log( 'arp_br_housekeeper_pkg.prev_posted_trh()+' );
1697 
1698  /*--------------------------------------------------+
1699   | Fetch previous posted transaction history record |
1700   +--------------------------------------------------*/
1701   OPEN prev_trh_cur;
1702   FETCH prev_trh_cur INTO p_trh_rec;
1703 
1704  /*-------------------------------------------------------------+
1705   | If previous posted transaction history record is not found, |
1706   | stop processing and raise an exception                      |
1707   +-------------------------------------------------------------*/
1708   IF prev_trh_cur%NOTFOUND THEN
1709     write_debug_and_log( 'Previous transaction history record cannot be found' );
1710     CLOSE prev_trh_cur;
1711     APP_EXCEPTION.raise_exception;
1712   END IF;
1713 
1714   CLOSE prev_trh_cur;
1715 
1716   write_debug_and_log( 'arp_br_housekeeper_pkg.prev_posted_trh()-' );
1717 
1718   EXCEPTION
1719     WHEN OTHERS THEN
1720       write_debug_and_log('Exception: arp_br_housekeeper_pkg.prev_posted_trh '||SQLERRM);
1721       RAISE;
1722 
1723 END prev_posted_trh;
1724 
1725 /*===========================================================================+
1726  | PROCEDURE fetch_remittance_setup_data                                     |
1727  |    	                                                                     |
1728  | DESCRIPTION                                                               |
1729  |    This function fetches Bills Receivable transaction setup data          |
1730  |    ie recovery days used by remittance                                    |
1731  |                                                                           |
1732  | SCOPE - PUBLIC                                                            |
1733  |                                                                           |
1734  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1735  |    arp_util.debug                                                         |
1736  |                                                                           |
1737  | ARGUMENTS  : IN                                                           |
1738  |               p_status   - BR transaction status                          |
1739  |               p_batch_id - Batch ID for remittance                        |
1740  |                                                                           |
1741  | MODIFICATION HISTORY                                                      |
1742  |     30-JUN-2000  Jani Rautiainen      Created                             |
1743  |                                                                           |
1744  +===========================================================================*/
1745 PROCEDURE fetch_remittance_setup_data(p_status             IN ar_transaction_history.status%TYPE,
1749   +------------------------------------------------*/
1746                                       p_batch_id           IN ar_batches.batch_id%TYPE DEFAULT NULL) IS
1747  /*------------------------------------------------+
1748   | Fetch remittance data from BR remittance batch |
1750   CURSOR remittance_setup_cur IS
1751     SELECT NVL(rma.br_collection_days,0) collection_days,
1752            NVL(rma.risk_elimination_days,0) risk_elimination_days,
1753            rm.receipt_inherit_inv_num_flag,
1754            ab.receipt_method_id,
1755            ab.remit_bank_acct_use_id,
1756            ab.batch_date
1757     FROM ar_batches ab, ar_receipt_method_accounts rma, ar_receipt_methods rm
1758     WHERE ab.batch_id           = p_batch_id
1759     and   rma.remit_bank_acct_use_id   = ab.remit_bank_acct_use_id
1760     and   rma.receipt_method_id = ab.receipt_method_id
1761     and   rm.receipt_method_id  = ab.receipt_method_id;
1762 
1763   remittance_setup_rec   remittance_setup_cur%ROWTYPE;
1764 
1765 BEGIN
1766 
1767   write_debug_and_log( 'arp_br_housekeeper_pkg.fetch_remittance_setup_data()' );
1768 
1769  /*-----------------------------+
1770   | Fetch remittance setup data |
1771   +-----------------------------*/
1772   OPEN remittance_setup_cur;
1773   FETCH remittance_setup_cur INTO remittance_setup_rec;
1774 
1775  /*----------------------------------------+
1776   | If remittance batch is not found, stop |
1777   | processing and raise an exception      |
1778   +----------------------------------------*/
1779   IF remittance_setup_cur%NOTFOUND THEN
1780 
1781     write_debug_and_log( 'Previous transaction history record cannot be found' );
1782     CLOSE remittance_setup_cur;
1783     APP_EXCEPTION.raise_exception;
1784 
1785   END IF;
1786 
1787   CLOSE remittance_setup_cur;
1788 
1789   IF p_status = 'REMITTED' THEN
1790 
1791    /*--------------------------------------------------------------------+
1792     | If processing BR with status REMITTED the collections days is used |
1793     +--------------------------------------------------------------------*/
1794     pg_collection_days              := remittance_setup_rec.collection_days;
1795     pg_risk_elimination_days        := NULL;
1796 
1797   ELSIF p_status = 'FACTORED' or p_status = 'MATURED_PEND_RISK_ELIMINATION' THEN
1798 
1799    /*-------------------------------------------------------------------------+
1800     | If processing BR with status FACTORED the risk elimination days is used |
1801     +-------------------------------------------------------------------------*/
1802     pg_collection_days              := NULL;
1803     pg_risk_elimination_days        := remittance_setup_rec.risk_elimination_days;
1804 
1805   ELSE
1806 
1807     write_debug_and_log( 'Status '|| p_status ||' not supported' );
1808     APP_EXCEPTION.raise_exception;
1809 
1810   END IF;
1811 
1812  /*--------------------------------------------+
1813   | Copy values to package global variables to |
1814   | make them visible to the sub procedures    |
1815   +--------------------------------------------*/
1816   pg_rct_inherit_inv_num_flag := remittance_setup_rec.receipt_inherit_inv_num_flag;
1817   pg_receipt_method_id        := remittance_setup_rec.receipt_method_id;
1818   pg_remit_bank_acct_use_id   := remittance_setup_rec.remit_bank_acct_use_id;
1819   pg_remittance_batch_date    := remittance_setup_rec.batch_date;
1820 
1821   EXCEPTION
1822     WHEN OTHERS THEN
1823       write_debug_and_log('Exception: arp_br_housekeeper_pkg.fetch_remittance_setup_data '||SQLERRM);
1824       RAISE;
1825 
1826 END fetch_remittance_setup_data;
1827 
1828 /*===========================================================================+
1829  | PROCEDURE fetch_endorsement_setup_data                                    |
1830  |    	                                                                     |
1831  | DESCRIPTION                                                               |
1832  |    This function fetches Bills Receivable transaction setup data          |
1833  |    ie recovery days used by endorsement                                   |
1834  |                                                                           |
1835  | SCOPE - PUBLIC                                                            |
1836  |                                                                           |
1837  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1838  |    arp_util.debug                                                         |
1839  |                                                                           |
1840  | ARGUMENTS  : IN                                                           |
1841  |               p_receivables_trx_id - Receivable activity for endorsement  |
1842  |                                                                           |
1843  | MODIFICATION HISTORY                                                      |
1844  |     30-JUN-2000  Jani Rautiainen      Created                             |
1845  |                                                                           |
1846  +===========================================================================*/
1847 PROCEDURE fetch_endorsement_setup_data(p_receivables_trx_id IN ar_receivables_trx.receivables_trx_id%TYPE) IS
1848 
1849  /*--------------------------------+
1850   | Fetch receivable activity data |
1851   +--------------------------------*/
1852   CURSOR endorsement_setup_cur IS
1853     SELECT NVL(rt.risk_elimination_days,0) risk_elimination_days
1854     FROM  ar_receivables_trx rt
1855     WHERE rt.receivables_trx_id = p_receivables_trx_id;
1856 
1860 
1857   endorsement_setup_rec endorsement_setup_cur%ROWTYPE;
1858 
1859 BEGIN
1861   write_debug_and_log( 'arp_br_housekeeper_pkg.fetch_endorsement_setup_data()' );
1862 
1863  /*----------------------------------------+
1864   | Fetch receivable activity setup_data   |
1865   +----------------------------------------*/
1866   OPEN endorsement_setup_cur;
1867   FETCH endorsement_setup_cur INTO endorsement_setup_rec;
1868 
1869  /*-------------------------------------------+
1870   | If receivable activity is not found, stop |
1871   | processing and raise an exception         |
1872   +-------------------------------------------*/
1873   IF endorsement_setup_cur%NOTFOUND THEN
1874 
1875     write_debug_and_log( 'Endorsement receivable activity cannot be found' );
1876     CLOSE endorsement_setup_cur;
1877     APP_EXCEPTION.raise_exception;
1878 
1879   END IF;
1880 
1881   CLOSE endorsement_setup_cur;
1882 
1883  /*--------------------------------------------+
1884   | Copy values to package global variables to |
1885   | make them visible to the sub procedures    |
1886   +--------------------------------------------*/
1887   pg_collection_days              := NULL;
1888   pg_risk_elimination_days        := endorsement_setup_rec.risk_elimination_days;
1889   pg_rct_inherit_inv_num_flag     := NULL;
1890   pg_receipt_method_id            := NULL;
1891   pg_remit_bank_acct_use_id       := NULL;
1892 
1893   EXCEPTION
1894     WHEN OTHERS THEN
1895       write_debug_and_log('Exception: arp_br_housekeeper_pkg.fetch_endorsement_setup_data '||SQLERRM);
1896       RAISE;
1897 
1898 END fetch_endorsement_setup_data;
1899 
1900 /*===========================================================================+
1901  | PROCEDURE write_API_output                                                |
1902  |    	                                                                     |
1903  | DESCRIPTION                                                               |
1904  |    Writes API output to the concurrent program log. Messages from the     |
1905  |    API can contain warnings and errors                                    |
1906  |                                                                           |
1907  | SCOPE - PUBLIC                                                            |
1908  |                                                                           |
1909  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1910  |    arp_util.debug                                                         |
1911  |                                                                           |
1912  | ARGUMENTS  : IN:  p_msg_count  - Number of messages from the API          |
1913  |                   p_msg_data   - Actual messages from the API             |
1914  |                                                                           |
1915  | RETURNS    : NONE                                                         |
1916  |                                                                           |
1917  | MODIFICATION HISTORY                                                      |
1918  |     17-APR-2000  Jani Rautiainen      Created                             |
1919  |                                                                           |
1920  +===========================================================================*/
1921 PROCEDURE write_API_output(p_msg_count        IN NUMBER,
1922                            p_msg_data         IN VARCHAR2) IS
1923 
1924   l_msg_data       VARCHAR2(2000);
1925 BEGIN
1926 
1927   IF p_msg_count  = 1 Then
1928    /*------------------------------------------------+
1929     | There is one message returned by the API, so it|
1930     | has been sent out in the parameter x_msg_data  |
1931     +------------------------------------------------*/
1932     write_debug_and_log(p_msg_data);
1933 
1934   ELSIF p_msg_count > 1 Then
1935    /*-------------------------------------------------------+
1936     | There are more than one messages returned by the API, |
1937     | so call them in a loop and print the messages         |
1938     +-------------------------------------------------------*/
1939 
1940     FOR l_count IN 1..p_msg_count LOOP
1941 
1942          l_msg_data := FND_MSG_PUB.Get(FND_MSG_PUB.G_NEXT,FND_API.G_FALSE);
1943          write_debug_and_log(to_char(l_count)||' : '||l_msg_data);
1944 
1945     END LOOP;
1946 
1947   END IF;
1948 
1949 EXCEPTION
1950   WHEN others THEN
1951    /*-------------------------------------------------------+
1952     | Error writing to the log, nothing we can do about it. |
1953     | Error is not raised since API messages also contain   |
1954     | non fatal warnings. If a real exception happened it   |
1955     | is handled on the calling routine.                    |
1956     +-------------------------------------------------------*/
1957     NULL;
1958 
1959 END write_API_output;
1960 
1961 /*===========================================================================+
1962  | PROCEDURE write_debug_and_log                                             |
1963  |    	                                                                     |
1964  | DESCRIPTION                                                               |
1965  |    Writes standard messages to standard debugging and to the log          |
1966  |                                                                           |
1967  | SCOPE - PUBLIC                                                            |
1968  |                                                                           |
1969  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
1973  |                                                                           |
1970  |    arp_util.debug                                                         |
1971  |                                                                           |
1972  | ARGUMENTS  : IN:  p_message - Message to be writted                       |
1974  | RETURNS    : NONE                                                         |
1975  |                                                                           |
1976  | MODIFICATION HISTORY                                                      |
1977  |     17-APR-2000  Jani Rautiainen      Created                             |
1978  |                                                                           |
1979  +===========================================================================*/
1980 PROCEDURE write_debug_and_log(p_message IN VARCHAR2) IS
1981 
1982 BEGIN
1983 
1984  /*------------------------------------------------+
1985   | Write the message to log and to the standard   |
1986   | debugging channel                              |
1987   +------------------------------------------------*/
1988   IF FND_GLOBAL.CONC_REQUEST_ID is not null THEN
1989 
1990    /*------------------------------------------------+
1991     | Only write to the log if call was made from    |
1992     | concurrent program.                            |
1993     +------------------------------------------------*/
1994     fnd_file.put_line(FND_FILE.LOG,p_message);
1995 
1996   END IF;
1997 
1998   IF PG_DEBUG in ('Y', 'C') THEN
1999      arp_standard.debug(p_message);
2000   END IF;
2001 
2002 EXCEPTION
2003   WHEN others THEN
2004    /*-------------------------------------------------------+
2005     | Error writing to the log, nothing we can do about it. |
2006     | Error is not raised since API messages also contain   |
2007     | non fatal warnings. If a real exception happened it   |
2008     | is handled on the calling routine.                    |
2009     +-------------------------------------------------------*/
2010     NULL;
2011 
2012 END write_debug_and_log;
2013 
2014 /*===========================================================================+
2015  | FUNCTION validate_and_default_gl_date                                     |
2016  |    	                                                                     |
2017  | DESCRIPTION                                                               |
2018  |    Validates and defaults GL date                                         |
2019  |                                                                           |
2020  | SCOPE - PUBLIC                                                            |
2021  |                                                                           |
2022  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
2023  |    arp_util.debug                                                         |
2024  |                                                                           |
2025  | ARGUMENTS:IN: p_gl_date          Date used in the                         |
2026  |               p_doc_date         arp_util.validate_and_default_gl_date    |
2027  |               p_validation_date1 to validate and / or default             |
2028  |               p_validation_date2 gl_date. For more information see        |
2029  |               p_validation_date3 ARP_STANDARD.validate_and_default_gl_date|
2030  |               p_default_date1                                             |
2031  |               p_default_date2                                             |
2032  |               p_default_date3                                             |
2033  |                                                                           |
2034  | RETURNS    : Defaulted GL_DATE                                            |
2035  |                                                                           |
2036  | MODIFICATION HISTORY                                                      |
2037  |     07-AUG-2000  Jani Rautiainen      Created                             |
2038  |                                                                           |
2039  +===========================================================================*/
2040 FUNCTION validate_and_default_gl_date(p_gl_date                in date,
2041                                       p_doc_date               in date,
2042                                       p_validation_date1       in date,
2043                                       p_validation_date2       in date,
2044                                       p_validation_date3       in date,
2045                                       p_default_date1          in date,
2046                                       p_default_date2          in date,
2047                                       p_default_date3          in date) RETURN DATE IS
2048 
2049   l_defaulting_rule_used       VARCHAR2(50);
2050   l_default_gl_date            DATE;
2051   l_error_message              VARCHAR2(240);
2052 
2053 BEGIN
2054   write_debug_and_log( 'arp_br_housekeeper_pkg.validate_and_default_gl_date()' );
2055 
2056  /*---------------------------------------------+
2057   | Validate GL date. If gl_date is not passed  |
2058   | try to default it                           |
2059   +---------------------------------------------*/
2060   IF (arp_util.validate_and_default_gl_date(p_gl_date,
2061                                             p_doc_date,
2062                                             p_validation_date1,
2063                                             p_validation_date2,
2064                                             p_validation_date3,
2065                                             p_default_date1,
2066                                             p_default_date2,
2067                                             p_default_date3,
2068                                             'N',
2069                                             NULL,
2070                                             arp_global.set_of_books_id,
2071                                             arp_global.G_AR_APP_ID,
2072                                             l_default_gl_date,
2073                                             l_defaulting_rule_used,
2074                                             l_error_message) = TRUE) THEN
2075 
2076         RETURN l_default_gl_date;
2077 
2078   ELSE
2079    /*-----------------------------------------------------+
2080     | Invalid GL_date and system was unable to default it |
2081     +-----------------------------------------------------*/
2085 
2082     write_debug_and_log( 'Invalid GL date' );
2083 
2084     RETURN to_date(NULL);
2086   END IF;
2087 
2088   EXCEPTION
2089     WHEN OTHERS THEN
2090 	write_debug_and_log('Exception: arp_br_housekeeper_pkg.validate_and_default_gl_date '||SQLERRM);
2091 	RAISE;
2092 
2093 END validate_and_default_gl_date;
2094 
2095 /*===========================================================================+
2096  | FUNCTION validate_against_doc_gl_date                                    |
2097  |    	                                                                     |
2098  | DESCRIPTION                                                               |
2099  |    Checks that the GL date is not before the transaction gl date          |
2100  |                                                                           |
2101  | SCOPE - PUBLIC                                                            |
2102  |                                                                           |
2103  | EXETERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
2104  |    arp_util.debug                                                         |
2105  |                                                                           |
2106  | ARGUMENTS:IN: p_gl_date          GL Date given as parameter to the report |
2107  |               p_doc_gl_date      Transaction GL Date                      |
2108  |                                                                           |
2109  | RETURNS    :  GL Date                                                     |
2110  |                                                                           |
2111  | MODIFICATION HISTORY                                                      |
2112  |     07-AUG-2000  Jani Rautiainen      Created                             |
2113  |                                                                           |
2114  +===========================================================================*/
2115 FUNCTION validate_against_doc_gl_date(p_gl_date                in date,
2116                                       p_doc_gl_date            in date) RETURN DATE IS
2117 
2118   l_default_gl_date            DATE;
2119 BEGIN
2120 
2121   write_debug_and_log( 'arp_br_housekeeper_pkg.validate_against_doc_gl_date()' );
2122 
2123  /*--------------------------------------------------------------+
2124   | If parameters are null return the Gl date given as parameter |
2125   | to the report as nothing was changed.                        |
2126   +--------------------------------------------------------------*/
2127   IF (p_gl_date is null or p_doc_gl_date is null) THEN
2128 
2129     RETURN pg_gl_date;
2130 
2131   END IF;
2132 
2133  /*------------------------------------------------------------------------+
2134   | If trx gl date is after the GL Date given as parameter to the report   |
2135   | we validate the trx gl date and use that as a GL Date. If trx GL date  |
2136   | id is not valid, then the GL_DATE will be defaulted to the last date of|
2137   | the most recent open period.                                           |
2138   +------------------------------------------------------------------------*/
2139   IF trunc(p_gl_date) < trunc(p_doc_gl_date) THEN
2140 
2141     l_default_gl_date := arp_br_housekeeper_pkg.validate_and_default_gl_date(p_doc_gl_date,
2142                                                                              NULL,NULL,NULL,NULL,NULL,NULL,NULL);
2143     IF l_default_gl_date is not NULL THEN
2144 
2145       write_debug_and_log( 'gl_date defaulted = '||to_char(l_default_gl_date));
2146       RETURN l_default_gl_date;
2147 
2148     ELSE
2149      /*-----------------------------------------------------+
2150       | Invalid GL_date and system was unable to default it |
2151       +-----------------------------------------------------*/
2152       write_debug_and_log( 'GL date could not be defaulted' );
2153       return p_gl_date;
2154 
2155     END IF;
2156 
2157   ELSE
2158    /*------------------------------------------------------------------------+
2159     | If trx GL date is before the GL date given as parameter to the report  |
2160     | we can use the given GL date directly                                  |
2161     +------------------------------------------------------------------------*/
2162     return p_gl_date;
2163 
2164   END IF;
2165 
2166   EXCEPTION
2167     WHEN OTHERS THEN
2168 	write_debug_and_log('Exception: arp_br_housekeeper_pkg.validate_against_doc_gl_date '||SQLERRM);
2169 	RAISE;
2170 
2171 END validate_against_doc_gl_date;
2172 
2173 END arp_br_housekeeper_pkg;