DBA Data[Home] [Help]

PACKAGE BODY: APPS.AR_PURGE

Source


1 PACKAGE BODY AR_PURGE AS
2 /* $Header: ARPURGEB.pls 120.34.12020000.4 2012/07/25 13:39:46 kkikkise ship $ */
3 
4     TYPE unpurgeable IS TABLE OF VARCHAR2(1) INDEX BY BINARY_INTEGER;
5     -- bug1199027
6     TYPE control_detail_rec IS RECORD
7     (
8         period_name                   VARCHAR2(15),
9         invoices_cnt                  NUMBER,
10         credit_memos_cnt              NUMBER,
11         debit_memos_cnt               NUMBER,
12         chargebacks_cnt               NUMBER,
13         deposits_cnt                  NUMBER,
14         adjustments_cnt               NUMBER,
15         cash_receipts_cnt             NUMBER,
16         invoices_no_rec_cnt           NUMBER,
17         credit_memos_no_rec_cnt       NUMBER,
18         debit_memos_no_rec_cnt        NUMBER,
19         chargebacks_no_rec_cnt        NUMBER,
20         deposits_no_rec_cnt           NUMBER,
21         guarantees_cnt                NUMBER,
22         misc_receipts_cnt             NUMBER,
23         invoices_total                NUMBER,
24         credit_memos_total            NUMBER,
25         debit_memos_total             NUMBER,
26         chargebacks_total             NUMBER,
27         deposits_total                NUMBER,
28         adjustments_total             NUMBER,
29         cash_receipts_total           NUMBER,
30         discounts_total               NUMBER,
31         exchange_gain_loss_total      NUMBER,
32         invoices_no_rec_total         NUMBER,
33         credit_memos_no_rec_total     NUMBER,
34         debit_memos_no_rec_total      NUMBER,
35         chargebacks_no_rec_total      NUMBER,
36         deposits_no_rec_total         NUMBER,
37         guarantees_total              NUMBER,
38         misc_receipts_total           NUMBER
39     ) ;
40     TYPE control_detail_array IS TABLE OF control_detail_rec INDEX BY BINARY_INTEGER ;
41 
42     l_unpurgeable_txns         unpurgeable;
43     l_unpurgeable_receipts     unpurgeable;
44     l_control_detail_array     control_detail_array ; --bug1199027
45 
46     /* bug3975105 added */
47     l_text varchar2(2000);
48     l_short_flag varchar2(1);
49 
50     /* bug3975105 added p_flag */
51     PROCEDURE print( p_indent IN NUMBER, p_text IN VARCHAR2, p_flag IN VARCHAR2 DEFAULT NULL ) IS
52     BEGIN
53 
54        /* Only unpurged log */
55        IF l_short_flag = 'Y' then
56 
57           /* if p_text has trx/rec info */
58           IF p_flag = 'Y' then
59              l_text := p_text ;
60 
61           /* if purge was done Successfully */
62           ELSIF p_flag = 'S' then
63              l_text := null;
64 
65           /* if p_text has process info */
66           ELSIF p_flag = 'N' then
67              null;
68 
69           /* if p_text has error info */
70           ELSIF p_flag is null then
71 
72              IF l_text is not null then
73                 fnd_file.put_line( FND_FILE.LOG, l_text );
74                 l_text := null;
75              END IF;
76 
77              fnd_file.put_line( FND_FILE.LOG, p_text );
78           END IF;
79 
80        /* All log */
81        ELSE
82 
83           fnd_file.put_line( FND_FILE.LOG, RPAD(' ', p_indent*2)||p_text );
84        END IF;
85 
86     END;
87     --
88     -- add the given customer_trx_id to the list of unpurgeable transactions
89     --
90     PROCEDURE add_to_unpurgeable_txns( p_customer_trx_id IN NUMBER ) IS
91     BEGIN
92         l_unpurgeable_txns( p_customer_trx_id ) := 'Y';
93     END;
94     --
95     -- returns TRUE if this transaction is in the unpurgeable transaction list
96     --     FALSE if it is not
97     --
98     FUNCTION in_unpurgeable_txn_list( p_customer_trx_id IN NUMBER ) RETURN BOOLEAN IS
99     BEGIN
100         IF p_customer_trx_id is not null and l_unpurgeable_txns( p_customer_trx_id ) = 'Y'
101         THEN
102             RETURN TRUE;
103         END IF;
104 
105         RETURN FALSE;
106 
107     EXCEPTION
108         WHEN NO_DATA_FOUND THEN
109             RETURN FALSE;
110         WHEN OTHERS THEN
111             print( 0, 'Failed while checking the unpurgeable_trxn list') ;
112             print( 0, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
113             RAISE;
114     END;
115     -- bug 1715258
116     --
117     -- add the given cash_receipt_id to the list of unpurgeable receipts
118     --
119     PROCEDURE add_to_unpurgeable_receipts( p_cash_receipt_id IN NUMBER ) IS
120     BEGIN
121         l_unpurgeable_receipts( p_cash_receipt_id ) := 'Y';
122     END;
123     -- bug 1715258
124     --
125     -- returns TRUE if this receipts is in the unpurgeable receipts list
126     --     FALSE if it is not
127     --
128     FUNCTION in_unpurgeable_receipt_list( p_cash_receipt_id IN NUMBER ) RETURN BOOLEAN IS
129     BEGIN
130         IF l_unpurgeable_receipts( p_cash_receipt_id ) = 'Y'
131         THEN
132             RETURN TRUE;
133         END IF;
134 
135         RETURN FALSE;
136 
137     EXCEPTION
138         WHEN NO_DATA_FOUND THEN
139             RETURN FALSE;
140         WHEN OTHERS THEN
141             print( 0, 'Failed while checking the unpurgeable_receipt list') ;
142             print( 0, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
143             RAISE;
144     END;
145 
146     --
147     -- get_period_name
148     --
149     FUNCTION get_period_name ( p_gl_date  IN DATE ) RETURN VARCHAR2  IS
150         l_period_name VARCHAR2(15) ;
151     BEGIN
152 
153          SELECT period_name
154          INTO   l_period_name
155          FROM   gl_period_statuses
156          WHERE  application_id = 222
157          AND    set_of_books_id = arp_standard.sysparm.set_of_books_id
158          AND    p_gl_date >= start_date
159          AND    p_gl_date <= end_date
160          AND    adjustment_period_flag = 'N' ;
161          -- there could be 2 records with enabled_flag = 'Y' and 'N'
162 
163          RETURN ( l_period_name ) ;
164 
165     EXCEPTION
166         WHEN NO_DATA_FOUND THEN
167             RETURN ('-9999') ;
168         WHEN OTHERS THEN
169             print( 1, '  ...Failed while getting the period name ');
170             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
171             RAISE ;
172 
173     END ;
174     --
175     -- bug1199027
176     FUNCTION ins_control_detail_table ( p_amount IN NUMBER,
177                                         p_type IN VARCHAR2,
178                                         p_open_rec IN VARCHAR2,
179                                         p_period_name IN VARCHAR2,
180                                         p_archive_id  IN NUMBER ) RETURN BOOLEAN IS
181        l_last_index            NUMBER ;
182        l_control_detail_index  NUMBER := 0 ;
183        I NUMBER ;
184     BEGIN
185 
186        l_last_index := l_control_detail_array.last ;
187 
188        IF l_last_index IS NOT NULL
189        THEN
190             FOR I in 1..l_last_index
191             LOOP
192                 IF l_control_detail_array(I).period_name = p_period_name
193                 THEN
194                     IF p_type = 'INV'
195                     THEN
196                         IF p_open_rec = 'Y'
197                         THEN
198                            l_control_detail_array(I).invoices_cnt :=
199                                 l_control_detail_array(I).invoices_cnt + 1 ;
200                            l_control_detail_array(I).invoices_total :=
201                                 l_control_detail_array(I).invoices_total + p_amount ;
202                         ELSE
203                            l_control_detail_array(I).invoices_no_rec_cnt :=
204                                 l_control_detail_array(I).invoices_no_rec_cnt + 1 ;
205                            l_control_detail_array(I).invoices_no_rec_total :=
206                                 l_control_detail_array(I).invoices_no_rec_total + p_amount ;
207                         END IF ;
208                     ELSIF p_type = 'CM'
209                     THEN
210                         IF p_open_rec = 'Y'
211                         THEN
212                            l_control_detail_array(I).credit_memos_cnt :=
213                                 l_control_detail_array(I).credit_memos_cnt + 1 ;
214                            l_control_detail_array(I).credit_memos_total :=
215                                 l_control_detail_array(I).credit_memos_total + p_amount ;
216                         ELSE
217                            l_control_detail_array(I).credit_memos_no_rec_cnt :=
218                                 l_control_detail_array(I).credit_memos_no_rec_cnt + 1 ;
219                            l_control_detail_array(I).credit_memos_no_rec_total :=
220                                 l_control_detail_array(I).credit_memos_no_rec_total + p_amount ;
221                         END IF ;
222                     ELSIF p_type = 'DM'
223                     THEN
224                         IF p_open_rec = 'Y'
225                         THEN
226                            l_control_detail_array(I).debit_memos_cnt :=
227                                 l_control_detail_array(I).debit_memos_cnt + 1 ;
228                            l_control_detail_array(I).debit_memos_total :=
229                                 l_control_detail_array(I).debit_memos_total + p_amount ;
230                         ELSE
231                            l_control_detail_array(I).debit_memos_no_rec_cnt :=
232                                 l_control_detail_array(I).debit_memos_no_rec_cnt + 1 ;
233                            l_control_detail_array(I).debit_memos_no_rec_total :=
234                                 l_control_detail_array(I).debit_memos_no_rec_total + p_amount ;
235                         END IF ;
236                     ELSIF p_type = 'CB'
237                     THEN
238                         IF p_open_rec = 'Y'
239                         THEN
240                            l_control_detail_array(I).chargebacks_cnt :=
241                                 l_control_detail_array(I).chargebacks_cnt + 1 ;
242                            l_control_detail_array(I).chargebacks_total :=
243                                 l_control_detail_array(I).chargebacks_cnt + p_amount ;
244                         ELSE
245                            l_control_detail_array(I).chargebacks_no_rec_cnt :=
246                                 l_control_detail_array(I).chargebacks_no_rec_cnt + 1 ;
247                            l_control_detail_array(I).chargebacks_no_rec_total :=
248                                 l_control_detail_array(I).chargebacks_no_rec_cnt + p_amount ;
249                         END IF ;
250                     ELSIF p_type = 'ADJ'
251                     THEN
252                         l_control_detail_array(I).adjustments_cnt :=
253                              l_control_detail_array(I).adjustments_cnt + 1 ;
254                         l_control_detail_array(I).adjustments_total :=
255                              l_control_detail_array(I).adjustments_total + p_amount ;
256                     ELSIF p_type = 'CASH'
257                     THEN
258                         l_control_detail_array(I).cash_receipts_cnt :=
259                              l_control_detail_array(I).cash_receipts_cnt + 1 ;
260                         -- Negating the Cash Receipts amount
261                         l_control_detail_array(I).cash_receipts_total :=
262                              l_control_detail_array(I).cash_receipts_total + (-1 * p_amount) ;
263                     ELSIF p_type = 'MISC'
264                     THEN
265                         l_control_detail_array(I).misc_receipts_cnt :=
266                              l_control_detail_array(I).misc_receipts_cnt + 1 ;
267                         l_control_detail_array(I).misc_receipts_total :=
268                              l_control_detail_array(I).misc_receipts_cnt + p_amount ;
269                     ELSIF p_type = 'DISC'
270                     THEN
271                         l_control_detail_array(I).discounts_total :=
272                              l_control_detail_array(I).discounts_total + (-1 * p_amount) ;
273                     ELSIF p_type = 'EXCH'
274                     THEN
275                         l_control_detail_array(I).exchange_gain_loss_total :=
276                              l_control_detail_array(I).exchange_gain_loss_total + p_amount ;
277                     END IF ;
278                     RETURN TRUE ;
279                 END IF ;
280             END LOOP ;
281        END IF ;
282        --
283        l_control_detail_index := NVL(l_last_index,0) + 1 ; -- Adding a new entry in the table
284        --
285        -- Initialising the values
286        --
287        l_control_detail_array(l_control_detail_index).invoices_cnt := 0 ;
288        l_control_detail_array(l_control_detail_index).credit_memos_cnt := 0 ;
289        l_control_detail_array(l_control_detail_index).debit_memos_cnt := 0 ;
290        l_control_detail_array(l_control_detail_index).chargebacks_cnt := 0 ;
291        l_control_detail_array(l_control_detail_index).adjustments_cnt := 0 ;
292        l_control_detail_array(l_control_detail_index).cash_receipts_cnt := 0 ;
293        l_control_detail_array(l_control_detail_index).invoices_no_rec_cnt := 0 ;
294        l_control_detail_array(l_control_detail_index).credit_memos_no_rec_cnt := 0 ;
295        l_control_detail_array(l_control_detail_index).debit_memos_no_rec_cnt := 0 ;
296        l_control_detail_array(l_control_detail_index).chargebacks_no_rec_cnt := 0 ;
297        l_control_detail_array(l_control_detail_index).misc_receipts_cnt := 0 ;
298        l_control_detail_array(l_control_detail_index).invoices_total := 0 ;
299        l_control_detail_array(l_control_detail_index).credit_memos_total := 0 ;
300        l_control_detail_array(l_control_detail_index).debit_memos_total := 0 ;
301        l_control_detail_array(l_control_detail_index).chargebacks_total := 0 ;
302        l_control_detail_array(l_control_detail_index).adjustments_total := 0 ;
303        l_control_detail_array(l_control_detail_index).cash_receipts_total := 0 ;
304        l_control_detail_array(l_control_detail_index).discounts_total := 0 ;
305        l_control_detail_array(l_control_detail_index).exchange_gain_loss_total := 0 ;
306        l_control_detail_array(l_control_detail_index).invoices_no_rec_total := 0 ;
307        l_control_detail_array(l_control_detail_index).credit_memos_no_rec_total := 0 ;
308        l_control_detail_array(l_control_detail_index).debit_memos_no_rec_total := 0 ;
309        l_control_detail_array(l_control_detail_index).chargebacks_no_rec_total := 0 ;
310        l_control_detail_array(l_control_detail_index).misc_receipts_total := 0 ;
311        --
312        l_control_detail_array(l_control_detail_index).period_name := p_period_name ;
313        --
314        IF p_type = 'INV'
315        THEN
316            IF p_open_rec = 'Y'
317            THEN
318               l_control_detail_array(l_control_detail_index).invoices_cnt := 1 ;
319               l_control_detail_array(l_control_detail_index).invoices_total := p_amount ;
320            ELSE
321               l_control_detail_array(l_control_detail_index).invoices_no_rec_cnt := 1 ;
322               l_control_detail_array(l_control_detail_index).invoices_no_rec_total := p_amount ;
323            END IF ;
324        ELSIF p_type = 'CM'
325        THEN
326            IF p_open_rec = 'Y'
327            THEN
328               l_control_detail_array(l_control_detail_index).credit_memos_cnt := 1 ;
329               l_control_detail_array(l_control_detail_index).credit_memos_total := p_amount ;
330            ELSE
331               l_control_detail_array(l_control_detail_index).credit_memos_no_rec_cnt := 1 ;
332               l_control_detail_array(l_control_detail_index).credit_memos_no_rec_total := p_amount ;
333            END IF ;
334        ELSIF p_type = 'DM'
335        THEN
336            IF p_open_rec = 'Y'
337            THEN
338               l_control_detail_array(l_control_detail_index).debit_memos_cnt := 1 ;
339               l_control_detail_array(l_control_detail_index).debit_memos_total := p_amount ;
340            ELSE
341               l_control_detail_array(l_control_detail_index).debit_memos_no_rec_cnt := 1 ;
342               l_control_detail_array(l_control_detail_index).debit_memos_no_rec_total := p_amount ;
343            END IF ;
344        ELSIF p_type = 'CB'
345        THEN
346            IF p_open_rec = 'Y'
347            THEN
348               l_control_detail_array(l_control_detail_index).chargebacks_cnt := 1 ;
349               l_control_detail_array(l_control_detail_index).chargebacks_total := p_amount ;
350            ELSE
351               l_control_detail_array(l_control_detail_index).chargebacks_no_rec_cnt := 1 ;
352               l_control_detail_array(l_control_detail_index).chargebacks_no_rec_total := p_amount ;
353            END IF ;
354        ELSIF p_type = 'ADJ'
355        THEN
356            l_control_detail_array(l_control_detail_index).adjustments_cnt := 1 ;
357            l_control_detail_array(l_control_detail_index).adjustments_total := p_amount ;
358        ELSIF p_type = 'CASH'
359        THEN
360            l_control_detail_array(l_control_detail_index).cash_receipts_cnt := 1 ;
361            -- Negating the Cash Receipts amount
362            l_control_detail_array(l_control_detail_index).cash_receipts_total := -1 * p_amount ;
363        ELSIF p_type = 'MISC'
364        THEN
365            l_control_detail_array(l_control_detail_index).misc_receipts_cnt := 1 ;
366            l_control_detail_array(l_control_detail_index).misc_receipts_total := p_amount ;
367        ELSIF p_type = 'DISC'
368        THEN
369            l_control_detail_array(l_control_detail_index).discounts_total := -1 * p_amount ;
370        ELSIF p_type = 'EXCH'
371        THEN
372            l_control_detail_array(l_control_detail_index).exchange_gain_loss_total := p_amount ;
373        END IF ;
374        --
375        RETURN(TRUE) ;
376 
377     EXCEPTION
378         WHEN OTHERS THEN
379            print( 1, '  ...Failed while ins into control_detail_table');
380            print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
381            RAISE ;
382     END ;
383     --
384     --
385     -- bug1199027
386     FUNCTION upd_arch_control_detail ( p_archive_id  IN NUMBER ) RETURN BOOLEAN IS
387        I NUMBER ;
388     BEGIN
389 
390        FOR I IN 1..l_control_detail_array.last
391        LOOP
392             UPDATE ar_archive_control_detail
393             SET    invoices_cnt              = invoices_cnt +
394                                                    l_control_detail_array(I).invoices_cnt ,
395                    credit_memos_cnt          = credit_memos_cnt +
396                                                    l_control_detail_array(I).credit_memos_cnt,
397                    debit_memos_cnt           = debit_memos_cnt +
398                                                    l_control_detail_array(I).debit_memos_cnt,
399                    chargebacks_cnt           = chargebacks_cnt +
400                                                    l_control_detail_array(I).chargebacks_cnt,
401                    adjustments_cnt           = adjustments_cnt +
402                                                    l_control_detail_array(I).adjustments_cnt,
403                    cash_receipts_cnt         = cash_receipts_cnt +                                                                                          l_control_detail_array(I).cash_receipts_cnt,
404                    invoices_no_rec_cnt       = invoices_no_rec_cnt +
405                                                    l_control_detail_array(I).invoices_no_rec_cnt,
406                    credit_memos_no_rec_cnt   = credit_memos_no_rec_cnt +
407                                                    l_control_detail_array(I).credit_memos_no_rec_cnt,
408                    debit_memos_no_rec_cnt    = debit_memos_no_rec_cnt +
409                                                    l_control_detail_array(I).debit_memos_no_rec_cnt,
410                    chargebacks_no_rec_cnt    = chargebacks_no_rec_cnt +
411                                                    l_control_detail_array(I).chargebacks_no_rec_cnt,
412                    misc_receipts_cnt         = misc_receipts_cnt +
413                                                    l_control_detail_array(I).misc_receipts_cnt,
414                    invoices_total            = invoices_total +
415                                                    l_control_detail_array(I).invoices_total,
416                    credit_memos_total        = credit_memos_total +
417                                                    l_control_detail_array(I).credit_memos_total,
418                    debit_memos_total         = debit_memos_total +
419                                                    l_control_detail_array(I).debit_memos_total,
420                    chargebacks_total         = chargebacks_total +
421                                                    l_control_detail_array(I).chargebacks_total,
422                    adjustments_total         = adjustments_total +
423                                                    l_control_detail_array(I).adjustments_total,
424                    -- Negating the Cash Receipts amount
425                    cash_receipts_total       = cash_receipts_total +
426                                                    l_control_detail_array(I).cash_receipts_total,
427                    discounts_total           = discounts_total +
428                                                    l_control_detail_array(I).discounts_total,
429                    exchange_gain_loss_total  = exchange_gain_loss_total +
430                                                    l_control_detail_array(I).exchange_gain_loss_total,
431                    invoices_no_rec_total     = invoices_no_rec_total +
432                                                    l_control_detail_array(I).invoices_no_rec_total,
433                    credit_memos_no_rec_total =  credit_memos_no_rec_total +
434                                                    l_control_detail_array(I).credit_memos_no_rec_total,
435                    debit_memos_no_rec_total  = debit_memos_no_rec_total +
436                                                    l_control_detail_array(I).debit_memos_no_rec_total,
437                    chargebacks_no_rec_total  = chargebacks_no_rec_total  +
438                                                    l_control_detail_array(I).chargebacks_no_rec_total,
439                    misc_receipts_total       = misc_receipts_total +
440                                                    l_control_detail_array(I).misc_receipts_total
441             WHERE  archive_id  = p_archive_id
442             AND    period_name = l_control_detail_array(I).period_name  ;
443 
444             IF SQL%ROWCOUNT = 0
445             THEN
446                 BEGIN
447 
448                     INSERT INTO ar_archive_control_detail
449                     ( archive_id,
450                       period_name,
451                       invoices_cnt,
452                       credit_memos_cnt,
453                       debit_memos_cnt,
454                       chargebacks_cnt,
455                       adjustments_cnt,
456                       cash_receipts_cnt,
457                       invoices_no_rec_cnt,
458                       credit_memos_no_rec_cnt,
459                       debit_memos_no_rec_cnt,
460                       chargebacks_no_rec_cnt,
461                       misc_receipts_cnt,
462                       invoices_total,
463                       credit_memos_total,
464                       debit_memos_total,
465                       chargebacks_total,
466                       adjustments_total,
467                       cash_receipts_total,
468                       discounts_total,
469                       exchange_gain_loss_total,
470                       invoices_no_rec_total,
471                       credit_memos_no_rec_total,
472                       debit_memos_no_rec_total,
473                       chargebacks_no_rec_total,
474                       misc_receipts_total,
475                       deposits_total,
476                       deposits_cnt
477                     )
478                     VALUES
479                     (
480                       lpad(p_archive_id,14,'0'), /* modified for the bug 3266428 */
481                       l_control_detail_array(I).period_name,
482                       l_control_detail_array(I).invoices_cnt,
483                       l_control_detail_array(I).credit_memos_cnt,
484                       l_control_detail_array(I).debit_memos_cnt,
485                       l_control_detail_array(I).chargebacks_cnt,
486                       l_control_detail_array(I).adjustments_cnt,
487                       l_control_detail_array(I).cash_receipts_cnt,
488                       l_control_detail_array(I).invoices_no_rec_cnt,
489                       l_control_detail_array(I).credit_memos_no_rec_cnt,
490                       l_control_detail_array(I).debit_memos_no_rec_cnt,
491                       l_control_detail_array(I).chargebacks_no_rec_cnt,
492                       l_control_detail_array(I).misc_receipts_cnt,
493                       l_control_detail_array(I).invoices_total,
494                       l_control_detail_array(I).credit_memos_total,
495                       l_control_detail_array(I).debit_memos_total,
496                       l_control_detail_array(I).chargebacks_total,
497                       l_control_detail_array(I).adjustments_total,
498                       l_control_detail_array(I).cash_receipts_total,
499                       l_control_detail_array(I).discounts_total,
500                       l_control_detail_array(I).exchange_gain_loss_total,
501                       l_control_detail_array(I).invoices_no_rec_total,
502                       l_control_detail_array(I).credit_memos_no_rec_total,
503                       l_control_detail_array(I).debit_memos_no_rec_total,
504                       l_control_detail_array(I).chargebacks_no_rec_total,
505                       l_control_detail_array(I).misc_receipts_total,
506                       l_control_detail_array(I).deposits_total,
507                       l_control_detail_array(I).deposits_cnt
508                     ) ;
509                 EXCEPTION
510                     WHEN OTHERS THEN
511                         print( 1, '  ...Failed while inserting into AR_ARCHIVE_CONTROL_DETAIL');
512                         print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
513                         RAISE ;
514                 END  ;
515             END IF ;
516 
517        END LOOP ;
518        RETURN(TRUE) ;
519 
520     EXCEPTION
521         WHEN NO_DATA_FOUND THEN
522              print( 1, '  ...Failed while ins/upd into AR_ARCHIVE_CONTROL_DETAIL');
523              RETURN(FALSE);
524         WHEN OTHERS THEN
525            print( 1, '  ...Failed while ins/upd into AR_ARCHIVE_CONTROL_DETAIL');
526            print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
527            RAISE ;
528     END ;
529     ---
530     FUNCTION trx_purgeable(p_entity_id IN NUMBER) RETURN BOOLEAN IS
531       allow_purge BOOLEAN := TRUE;
532     BEGIN
533     --
534     --  Place your logic here. Set the value of allow_purge to TRUE if
535     --  you want this invoice to be purged, or FALSE if you don't want it
536     --  purged
537         RETURN allow_purge;
538     END;
539     ---
540     --- FUNCTION get_ccid
541     --- Function to get concatenated segments for a code combination id
542     ---
543     FUNCTION get_ccid  (p_code_combination_id  NUMBER) RETURN VARCHAR2 IS
544         l_account_segs    VARCHAR2(240);
545 
546     BEGIN
547 
548   SELECT RTRIM(
549     cc.segment1 || '.' ||
550     cc.segment2 || '.' ||
551     cc.segment3 || '.' ||
552     cc.segment4 || '.' ||
553     cc.segment5 || '.' ||
554     cc.segment6 || '.' ||
555     cc.segment7 || '.' ||
556     cc.segment8 || '.' ||
557     cc.segment9 || '.' ||
558     cc.segment10 || '.' ||
559     cc.segment11 || '.' ||
560     cc.segment12 || '.' ||
561     cc.segment13 || '.' ||
562     cc.segment14 || '.' ||
563     cc.segment15 || '.' ||
564     cc.segment16 || '.' ||
565     cc.segment17 || '.' ||
566     cc.segment18 || '.' ||
567     cc.segment19 || '.' ||
568     cc.segment20 || '.' ||
569     cc.segment21 || '.' ||
570     cc.segment22 || '.' ||
571     cc.segment23 || '.' ||
572     cc.segment24 || '.' ||
573     cc.segment25 || '.' ||
574     cc.segment26 || '.' ||
575     cc.segment27 || '.' ||
576     cc.segment28 || '.' ||
577     cc.segment29 || '.' ||
578     cc.segment30, '.' )
579    INTO    l_account_segs
580   FROM    gl_code_combinations cc
581   WHERE   cc.code_combination_id = p_code_combination_id;
582 
583         RETURN(l_account_segs);
584 
585     EXCEPTION
586         WHEN NO_DATA_FOUND THEN
587             RETURN NULL ;
588         WHEN OTHERS THEN
589             print( 1, 'Failed while selecting from gl_code_combinations') ;
590             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
591             RAISE ;
592     END get_ccid;
593 
594     --Add for bug 13582725
595     FUNCTION archive_rev_receipt (p_cash_receipt_id IN NUMBER ,
596                                   p_archive_id      IN NUMBER,
597                                   p_archive_level   IN  VARCHAR2)
598     RETURN BOOLEAN is
599     BEGIN
600          DECLARE
601          CURSOR header_cursor ( cp_cash_receipt_id NUMBER,cp_archive_level varchar2) IS
602                SELECT cr.type type,      /* transaction_class */
603                '' name,              /* transaction_type */
604                cr.cash_receipt_id trx_id,   /* transaction_id */
605                '' related_trx_type,    /* related_transaction_class */
606                '' related_trx_id,    /* related_transaction_type */
607                to_number('') prev_trx_id,   /* related_transaction_id */
608                cr.receipt_number trx_number,  /* transaction_number */
609                cr.receipt_date trx_date,  /* transaction_date */
610                batch.name batch_name,
611                bs.name    batch_source_name,
612                sob.name   sob_name,
613                cr.amount  amount,
614                -- bug1199027
615                sum( ra.acctd_amount_applied_to ) acctd_amount,/* acctd_amount */
616                sum( ra.acctd_amount_applied_from - ra.acctd_amount_applied_to )
617                         exch_gain_loss, /* exchange_gain_loss */
618                sum( ra.earned_discount_taken ) earned_disc_taken ,
619                sum( ra.unearned_discount_taken ) unearned_disc_taken ,
620                sum( ra.acctd_earned_discount_taken ) acctd_earned_disc_taken ,
621                sum( ra.acctd_unearned_discount_taken ) acctd_unearned_disc_taken ,
622                cr.type adj_trx_type,
623                '' adj_type,      /* adjustment_type */
624                ''  post_to_gl,                  /* post_to_gl */
625                ''  open_receivable,             /* accounting_affect_flag */
626                cr.status cash_rcpt_status,  /* cash_receipt_status */
627                crh.status cash_rcpt_hist_status,/* cash_receipt_history_status */
628                '' reason_code,                 /* reason_code_meaning */
629                substrb(cust_party.party_name,1,50)  bill_to_cust_name,    /* bill_to_customer_name */
630                cust.account_number bill_to_cust_no,          /* bill_to_customer_number */
631                su.location bill_to_cust_loc,      /* bill_to_customer_location */
632                substrb(loc.address1, 1, 80) bill_to_cust_addr1, /* bill_to_customer_address1 */
633                substrb(loc.address2, 1, 80) bill_to_cust_addr2, /* bill_to_customer_address2 */
634                substrb(loc.address3, 1, 80) bill_to_cust_addr3, /* bill_to_customer_address3 */
635                substrb(loc.address4, 1, 80) bill_to_cust_addr4, /* bill_to_customer_address4 */
636                loc.city  bill_to_cust_city,      /* bill_to_customer_city */
637                loc.state bill_to_cust_state,      /* bill_to_customer_state */
638                loc.country bill_to_cust_country,               /* bill_to_customer_country */
639                loc.postal_code bill_to_cust_zip,    /* bill_to_postal_code*/
640                '' ship_to_cust_name,    /* ship_to_customer_name */
641                '' ship_to_cust_no,     /* ship_to_customer_number */
642                '' ship_to_cust_loc,     /* ship_to_customer_location */
643                '' ship_to_cust_addr1,     /* ship_to_customer_address1 */
644                '' ship_to_cust_addr2,     /* ship_to_customer_address2 */
645                '' ship_to_cust_addr3,    /* ship_to_customer_address3 */
646                '' ship_to_cust_addr4,     /* ship_to_customer_address4 */
647                '' ship_to_cust_city,     /* ship_to_customer_city */
648                '' ship_to_cust_state,     /* ship_to_customer_state */
649                '' ship_to_cust_country,   /* ship_to_customer_country */
650                '' ship_to_cust_zip,    /* ship_to_customer_postal_code */
651                '' remit_to_cust_addr1,    /* remit_to_customer_address1 */
652                '' remit_to_cust_addr2,    /* remit_to_customer_address2 */
653                '' remit_to_cust_addr3,    /* remit_to_customer_address3 */
654                '' remit_to_cust_addr4,    /* remit_to_customer_address4 */
655                '' remit_to_cust_city,     /* remit_to_customer_city */
656                '' remit_to_cust_state,     /* remit_to_customer_state */
657                '' remit_to_cust_country,   /* remit_to_customer_country */
658                '' remit_to_cust_zip,     /* remit_to_customer_postal_code */
659                '' salesrep_name,     /* salesrep_name */
660                '' term_name,       /* term_name */
661                to_date(NULL) term_due_date,  /* term_due_date */
662                to_date(NULL) last_printed,  /* printing_last_printed */
663                '' printing_option,      /* printing_option */
664                '' purchase_order,      /* purchase_order */
665                cr.comments comments,
666                cr.exchange_rate_type exch_rate_type,
667                cr.exchange_date exch_date,
668                cr.exchange_rate exch_rate,
669                cr.currency_code curr_code,
670                nvl(crh.gl_date, cr.receipt_date) gl_date,
671                cr.reversal_date reversal_date,
672                substrb(lu1.meaning, 1, 20) reversal_category,   /* reversal_category */
673                lu2.meaning reversal_reason_code,           /* reversal_reason_code_meaning */
674                cr.reversal_comments reversal_comments,
675                substrb(cr.attribute_category, 1, 30) attr_category,
676                cr.attribute1 attr1,
677                cr.attribute2 attr2,
678                cr.attribute3 attr3,
679                cr.attribute4 attr4,
680                cr.attribute5 attr5,
681                cr.attribute6 attr6,
682                cr.attribute7 attr7,
683                cr.attribute8 attr8,
684                cr.attribute9 attr9,
685                cr.attribute10 attr10,
686                cr.attribute11 attr11,
687                cr.attribute12 attr12,
688                cr.attribute13 attr13,
689                cr.attribute14 attr14,
690                cr.attribute15 attr15,
691                rm.name rcpt_method,    /* receipt_method_name */
692                '' waybill_no,      /* waybill_number */
693                doc.name doc_name,
694                cr.doc_sequence_value doc_seq_value,
695                to_date(NULL) st_date_commitment,    /* start_date_commitment */
696                to_date(NULL) en_date_commitment,    /* end_date_commitment */
697                ''  invoicing_rule,
698                ba.bank_account_name  bank_acct_name,
699                cr.deposit_date deposit_date,
700                cr.factor_discount_amount factor_disc_amount,
701                '' int_hdr_context,      /* interface_header_context */
702                '' int_hdr_attr1,        /* interface_header_attribute1 */
703                '' int_hdr_attr2,  /* interface_header_attribute2 */
704                '' int_hdr_attr3,  /* interface_header_attribute3 */
705                '' int_hdr_attr4,  /* interface_header_attribute4 */
706                '' int_hdr_attr5,  /* interface_header_attribute5 */
707                '' int_hdr_attr6,  /* interface_header_attribute6 */
708                '' int_hdr_attr7,  /* interface_header_attribute7 */
709                '' int_hdr_attr8,  /* interface_header_attribute8 */
710                '' int_hdr_attr9,  /* interface_header_attribute9 */
711                '' int_hdr_attr10,  /* interface_header_attribute10 */
712                '' int_hdr_attr11,  /* interface_header_attribute11 */
713                '' int_hdr_attr12,  /* interface_header_attribute12 */
714                '' int_hdr_attr13,  /* interface_header_attribute13 */
715                '' int_hdr_attr14,  /* interface_header_attribute14 */
716                '' int_hdr_attr15,   /* interface_header_attribute15 */
717                batch_remit.bank_deposit_number bank_deposit_no,
718                cr.reference_type reference_type,
719                cr.reference_id reference_id,
720                cr.customer_receipt_reference cust_rcpt_reference,
721                ba2.bank_account_name bank_acct_name2
722         FROM   ar_lookups lu1,
723                ar_lookups lu2,
724                ap_bank_accounts  ba2,
725                ap_bank_accounts  ba,
726                ar_receipt_methods rm,
727                ar_batch_sources  bs,
728                ar_batches        batch,
729                ar_batches        batch_remit,
730                fnd_document_sequences doc,
731                gl_sets_of_books  sob,
732                hz_cust_acct_sites addr,
733                hz_party_sites     party_site,
734                hz_locations       loc,
735                hz_cust_site_uses su,
736                hz_cust_accounts  cust,
737                hz_parties        cust_party,
738                ar_receivable_applications ra,
739                ar_receivable_applications ra1, --bug1199027
740                ar_cash_receipt_history crh,
741                ar_cash_receipt_history crh_batch,
742                ar_cash_receipt_history crh_remit,
743                ar_cash_receipts  cr
744         WHERE  lu1.lookup_code (+)  = cr.reversal_category
745         AND    lu1.lookup_type (+)  = 'REVERSAL_CATEGORY_TYPE'
746         AND    lu2.lookup_code (+)  = cr.reversal_reason_code
747         AND    lu2.lookup_type (+)  = 'CKAJST_REASON'
748         AND    ba.bank_account_id (+)  = cr.customer_bank_account_id
749         AND    ba2.bank_account_id (+)      = cr.remittance_bank_account_id
750         AND    rm.receipt_method_id (+)     = cr.receipt_method_id
751         AND    cust.cust_account_id (+)     = cr.pay_from_customer
752         AND    cust.party_id                = cust_party.party_id(+)
753         AND    su.site_use_id (+)           = cr.customer_site_use_id
754         AND    addr.cust_acct_site_id (+)   = su.cust_acct_site_id
755         AND    addr.party_site_id           = party_site.party_site_id(+)
756         AND    loc.location_id (+)          = party_site.location_id
757         AND    doc.doc_sequence_id (+)      = cr.doc_sequence_id
758         AND    sob.set_of_books_id          = cr.set_of_books_id
759                /* get CR batch info */
760         AND    bs.batch_source_id (+)       = batch.batch_source_id
761         AND    batch.batch_id (+)           = crh_batch.batch_id
762         AND    crh_batch.first_posted_record_flag = 'Y'
763         AND    crh_batch.cash_receipt_id    = cr.cash_receipt_id
764                /* get current crh record for gl_date */
765         AND    crh.cash_receipt_id          = cr.cash_receipt_id
766         AND    crh.current_record_flag      = 'Y'
767                /* get remittance batch */
768         AND    crh_remit.batch_id           = batch_remit.batch_id(+)
769         AND    nvl(crh_remit.cash_receipt_history_id, -99) in
770                    ( SELECT nvl( min(crh1.cash_receipt_history_id), -99 )
771                      from   ar_cash_receipt_history crh1
772                      where  crh1.cash_receipt_id  = cr.cash_receipt_id
773                      and    crh1.status = 'REMITTED' )
774         AND    crh_remit.status (+)         = 'REMITTED'
775         AND    crh_remit.cash_receipt_id(+) = cr.cash_receipt_id
776         AND    cr.cash_receipt_id           = ra.cash_receipt_id
777         -- bug1199027
778         and    ra.cash_receipt_id           = ra1.cash_receipt_id
779         and    ra.status = ra1.status
780         and    ra1.cash_receipt_id  = cp_cash_receipt_id
781         and    ra1.status = 'APP'
782         -- bug2859402 Don't insert duplicate cash record.
783         and    not exists (
784                   select /*+ index(aah ar_archive_header_n1) */ 'already purged'
785                     from ar_archive_header aah
786                    where aah.transaction_id = cr.cash_receipt_id
787                      and aah.transaction_class = 'CASH' )
788        AND  cp_archive_level <>'N'
789         GROUP BY cr.type,      /* transaction_class */
790                  cr.cash_receipt_id,     /* transaction_id */
791                  cr.receipt_number,    /* transaction_number */
792                  cr.receipt_date,    /* transaction_date */
793                  batch.name,
794                  bs.name,
795                  sob.name,
796                  cr.amount,
797                  cr.type,
798                  cr.status,      /* cash_receipt_status */
799                  crh.status,      /* cash_receipt_history_status */
800                  cust_party.party_name,    /* bill_to_customer_name */
801                  cust.account_number,    /* bill_to_customer_number */
802                  su.location,      /* bill_to_customer_location */
803                  substrb(loc.address1, 1, 80),   /* bill_to_customer_address1 */
804                  substrb(loc.address2, 1, 80),  /* bill_to_customer_address2 */
805                  substrb(loc.address3, 1, 80),   /* bill_to_customer_address3 */
806                  substrb(loc.address4, 1, 80),   /* bill_to_customer_address4 */
807                  loc.city,      /* bill_to_customer_city */
808                  loc.state,      /* bill_to_customer_state */
809                  loc.country,      /* bill_to_customer_country */
810                  loc.postal_code,    /* bill_to_customer_postal_code */
811                  cr.comments,
812                  cr.exchange_rate_type,
813                  cr.exchange_date,
814                  cr.exchange_rate,
815                  cr.currency_code,
816                  nvl(crh.gl_date, cr.receipt_date),
817                  cr.reversal_date,
818                  substrb(lu1.meaning, 1, 20),   /* reversal_category */
819                  lu2.meaning,           /* reversal_reason_code_meaning */
820                  cr.reversal_comments,
821                  substrb(cr.attribute_category, 1, 30),
822                  cr.attribute1,
823                  cr.attribute2,
824                  cr.attribute3,
825                  cr.attribute4,
826                  cr.attribute5,
827                  cr.attribute6,
828                  cr.attribute7,
829                  cr.attribute8,
830                  cr.attribute9,
831                  cr.attribute10,
832                  cr.attribute11,
833                  cr.attribute12,
834                  cr.attribute13,
835                  cr.attribute14,
836                  cr.attribute15,
837                  rm.name,      /* receipt_method_name */
838                  doc.name,
839                  cr.doc_sequence_value,
840                  ba.bank_account_name,
841                  cr.deposit_date,
842                  cr.factor_discount_amount,
843                  batch_remit.bank_deposit_number,
844                  cr.reference_type,
845                  cr.reference_id,
846                  cr.customer_receipt_reference,
847                  ba2.bank_account_name  ;
848 
849     CURSOR detail_cursor ( cp_cash_receipt_id NUMBER, cp_archive_level VARCHAR2) IS
850                   SELECT
851          cr.type trx_class,       /* transaction_class */
852          '' trx_type,        /* transaction_type */
853          cr.cash_receipt_id trx_id,    /* transaction_id */
854          to_number('') line_id,      /* transaction_line_id */
855          ctt.type related_trx_class,      /* related_transaction_class */
856          ctt.name related_trx_type,      /* related_transaction_type */
857          ct.customer_trx_id related_trx_id,    /* related_transaction_id */
858          to_number('') related_trx_line_id,      /* related_transaction_line_id */
859          to_number('') line_number,        /* line_number */
860          'REC_APP' dist_type,       /* distribution_type */
861          ra.application_type app_type,    /* application_type */
862          '' line_code_meaning,         /* line_code_meaning */
863          '' description,        /* description */
864          '' item_name,        /* item_name */
865          to_number('') qty,      /* quantity */
866          to_number('') selling_price,      /* unit_selling_price */
867          '' line_type,        /* line_type */
868          ra.attribute_category attr_category,
869          ra.attribute1 attr1,
870          ra.attribute2 attr2,
871          ra.attribute3 attr3,
872          ra.attribute4 attr4,
873          ra.attribute5 attr5,
874          ra.attribute6 attr6,
875          ra.attribute7 attr7,
876          ra.attribute8 attr8,
877          ra.attribute9 attr9,
878          ra.attribute10 attr10,
879          ra.attribute11 attr11,
880          ra.attribute12 attr12,
881          ra.attribute13 attr13,
882          ra.attribute14 attr14,
883          ra.attribute15 attr15,
884          ra.amount_applied amount, /* amount */
885          to_number('') acctd_amount,      /* acctd_amount */
886          '' uom_code,            /* uom code */
887          cr.ussgl_transaction_code ussgl_trx_code,
888          to_number('') tax_rate,    /* tax_rate */
889          '' tax_code,         /* tax_code */
890          to_number('') tax_precedence,      /* tax_precedence */
891          ra.code_combination_id ccid1,    /* account_ccid1 */
892          to_number('') ccid2,        /* account_ccid2 */
893          ra.earned_discount_ccid ccid3,   /* account_ccid3 */
894          ra.unearned_discount_ccid ccid4, /* account_ccid4 */
895          ra.gl_date gl_date,
896          ra.gl_posted_date gl_posted_date,
897          '' rule_name,         /* acct_rule_name */
898          to_number('') acctg_rule_duration,/* rule_duration */
899          to_date(NULL) rule_start_date,      /* rule_start_date */
900          to_number('') last_period_to_credit,  /* last_period_to_credit */
901          ra.comments line_comment,     /* line_comment */
902          to_number('') line_adjusted,          /* line_adjusted */
903          to_number('') freight_adjusted,  /* freight_adjusted */
904          to_number('') tax_adjusted,    /* tax_adjusted */
905          to_number('') charges_adjusted,  /* receivables_charges_adjusted */
906          ra.line_applied line_applied,    /* line_applied */
907          ra.freight_applied freight_applied,  /* freight_applied */
908          ra.tax_applied tax_applied,    /* tax_applied */
909          ra.receivables_charges_applied charges_applied,/* receivables_charges_applied */
910          ra.earned_discount_taken earned_disc_taken,   /* earned_discount_taken */
911          ra.unearned_discount_taken unearned_disc_taken,/* unearned_discount_taken */
912          ra.acctd_amount_applied_from acctd_amount_applied_from,
913                 /* acctd_amount_applied_from */
914          ra.acctd_amount_applied_to acctd_amount_applied_to,
915                 /* acctd_amount_applied_to */
916          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
917                 /* acctd_earned_disc_taken */
918          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
919                 /* acctd_unearned_disc_taken */
920          to_number('') factor_discount_amount,	/* factor_discount_amount */
921          to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
922          '' int_line_context,    		/* interface_line_context */
923          '' int_line_attr1,   			/* interface_line_attribute1 */
924          '' int_line_attr2,  			/* interface_line_attribute2 */
925          '' int_line_attr3,   			/* interface_line_attribute3 */
926          '' int_line_attr4,   			/* interface_line_attribute4 */
927          '' int_line_attr5,   			/* interface_line_attribute5 */
928          '' int_line_attr6,   			/* interface_line_attribute6 */
929          '' int_line_attr7,   			/* interface_line_attribute7 */
930          '' int_line_attr8,   			/* interface_line_attribute8 */
931          '' int_line_attr9,   			/* interface_line_attribute9 */
932          '' int_line_attr10,   		/* interface_line_attribute10 */
933          '' int_line_attr11,   		/* interface_line_attribute11 */
934          '' int_line_attr12,  			/* interface_line_attribute12 */
935          '' int_line_attr13,  			/* interface_line_attribute13 */
936          '' int_line_attr14,  			/* interface_line_attribute14 */
937          '' int_line_attr15,    		/* interface_line_attribute15 */
938          '' exch_rate_type,			/* exchange_rate_type */
939          to_date(NULL) exch_date,  		/* exchange_date */
940          to_number('') exch_rate,		/* exchange_rate */
941          ps.due_date due_date,
942          ra.apply_date apply_date,
943          to_number('') movement_id,		/* movement_id */
944          '' vendor_return_code,		/* tax_vendor_return_code */
945          '' tax_auth_tax_rate,			/* tax_authority_tax_rates */
946          '' tax_exempt_flag,			/* tax_exemption_flag */
947          to_number('') tax_exemption_id,	/* tax_exemption_id */
948          '' exemption_type,			/* exemption_type */
949          '' tax_exemption_reason,              /* exemption_reason */
950          '' tax_exemption_number,		/* customer_exemption_number */
951          '' item_exception_rate,		/* item_exception_rate */
952          '' meaning 		                /* item_exception_reason */
953          FROM
954          ra_cust_trx_types ctt,
955          ar_payment_schedules ps,
956          ar_cash_receipts  cr,
957          ar_receivable_applications ra,
958          ra_customer_trx   ct,
959          (SELECT distinct cash_Receipt_id
960          FROM   ar_receivable_applications
961          WHERE  cash_receipt_id = cp_cash_receipt_id) ra1
962          WHERE   ctt.cust_trx_type_id    = ct.cust_trx_type_id
963          and 	ps.payment_schedule_id (+) = ra.applied_payment_schedule_id
964          and 	cr.cash_receipt_id     = ra.cash_receipt_id
965          and 	ra.applied_customer_trx_id = ct.customer_trx_id
966          and    ra.cash_receipt_id = ra1.cash_Receipt_id /*bug 6058203*/
967         -- bug3567865 Don't insert duplicate cash record.
968         and    not exists (
969                   select /* index(aad ar_archive_details_n1) */ 'already purged'
970                     from ar_archive_detail aad
971                    where aad.transaction_id = cr.cash_receipt_id
972                      and aad.transaction_class = 'CASH' )
973         AND cp_archive_level not in ('N','H');
974 
975         l_total_discount  NUMBER ;
976         l_period_name     VARCHAR2(15) ;
977         l_status          BOOLEAN ;
978          l_account_combination1 VARCHAR2(240) ;
979          l_account_combination2 VARCHAR2(240) ;
980          l_account_combination3 VARCHAR2(240) ;
981          l_account_combination4 VARCHAR2(240) ;
982         BEGIN
983 
984             FOR select_header IN header_cursor ( p_cash_receipt_id, p_archive_level )
985             LOOP
986              l_period_name := get_period_name ( select_header.gl_date ) ;
987 
988                  BEGIN
989 
990                      INSERT INTO ar_archive_header
991                      ( archive_id,
992                        transaction_class,
993                        transaction_type,
994                        transaction_id,
995                        related_transaction_class,
996                        related_transaction_type,
997                        related_transaction_id,
998                        transaction_number,
999                        transaction_date,
1000                        batch_name,
1001                        batch_source_name,
1002                        set_of_books_name,
1003                        amount,
1004                        -- acctd_amount, -- bug1199027
1005                        exchange_gain_loss,
1006                        earned_discount_taken,
1007                        unearned_discount_taken,
1008                        -- acctd_earned_discount_taken, -- bug1199027
1009                        -- acctd_unearned_discount_taken, -- bug1199027
1010                        type,
1011                        adjustment_type,
1012                        post_to_gl,
1013                        accounting_affect_flag,
1014                        cash_receipt_status,
1015                        cash_receipt_history_status,
1016                        reason_code_meaning,
1017                        bill_to_customer_name,
1018                        bill_to_customer_number,
1019                        bill_to_customer_location,
1020                        bill_to_customer_address1,
1021                        bill_to_customer_address2,
1022                        bill_to_customer_address3,
1023                        bill_to_customer_address4,
1024                        bill_to_customer_city,
1025                        bill_to_customer_state,
1026                        bill_to_customer_country,
1027                        bill_to_customer_postal_code,
1028                        ship_to_customer_name,
1029                        ship_to_customer_number,
1030                        ship_to_customer_location,
1031                        ship_to_customer_address1,
1032                        ship_to_customer_address2,
1033                        ship_to_customer_address3,
1034                        ship_to_customer_address4,
1035                        ship_to_customer_city,
1036                        ship_to_customer_state,
1037                        ship_to_customer_country,
1038                        ship_to_customer_postal_code,
1039                        remit_to_address1,
1040                        remit_to_address2,
1041                        remit_to_address3,
1042                        remit_to_address4,
1043                        remit_to_city,
1044                        remit_to_state,
1045                        remit_to_country,
1046                        remit_to_postal_code,
1047                        salesrep_name,
1048                        term_name,
1049                        term_due_date,
1050                        printing_last_printed,
1051                        printing_option,
1052                        purchase_order,
1053                        comments,
1054                        exchange_rate_type,
1055                        exchange_rate_date,
1056                        exchange_rate,
1057                        currency_code,
1058                        gl_date,
1059                        reversal_date,
1060                        reversal_category,
1061                        reversal_reason_code_meaning,
1062                        reversal_comments,
1063                        attribute_category,
1064                        attribute1,
1065                        attribute2,
1066                        attribute3,
1067                        attribute4,
1068                        attribute5,
1069                        attribute6,
1070                        attribute7,
1071                        attribute8,
1072                        attribute9,
1073                        attribute10,
1074                        attribute11,
1075                        attribute12,
1076                        attribute13,
1077                        attribute14,
1078                        attribute15,
1079                        receipt_method_name,
1080                        waybill_number,
1081                        document_sequence_name,
1082                        document_sequence_value,
1083                        start_date_commitment,
1084                        end_date_commitment,
1085                        invoicing_rule_name,
1086                        customer_bank_account_name,
1087                        deposit_date,
1088                        factor_discount_amount,
1089                        interface_header_context,
1090                        interface_header_attribute1,
1091                        interface_header_attribute2,
1092                        interface_header_attribute3,
1093                        interface_header_attribute4,
1094                        interface_header_attribute5,
1095                        interface_header_attribute6,
1096                        interface_header_attribute7,
1097                        interface_header_attribute8,
1098                        interface_header_attribute9,
1099                        interface_header_attribute10,
1100                        interface_header_attribute11,
1101                        interface_header_attribute12,
1102                        interface_header_attribute13,
1103                        interface_header_attribute14,
1104                        interface_header_attribute15,
1105                        bank_deposit_number,
1106                        reference_type,
1107                        reference_id,
1108                        customer_receipt_reference,
1109                        bank_account_name
1110                      )
1111                      VALUES
1112                      ( lpad(p_archive_id,14,'0'), /* modified for bug 3266428 */
1113                        select_header.type,
1114                        select_header.name,
1115                        select_header.trx_id,
1116                        select_header.related_trx_type,
1117                        select_header.related_trx_id,
1118                        select_header.prev_trx_id ,
1119                        select_header.trx_number,
1120                        select_header.trx_date,
1121                        select_header.batch_name,
1122                        select_header.batch_source_name,
1123                        select_header.sob_name,
1124                        select_header.amount,
1125                        -- select_header.acctd_amount, --bug1199027
1126                        select_header.exch_gain_loss,
1127                        select_header.earned_disc_taken,
1128                        select_header.unearned_disc_taken,
1129                        -- select_header.acctd_earned_disc_taken, --bug1199027
1130                        -- select_header.acctd_unearned_disc_taken, --bug1199027
1131                        select_header.adj_trx_type,
1132                        select_header.adj_type,
1133                        select_header.post_to_gl,
1134                        select_header.open_receivable,
1135                        select_header.cash_rcpt_status,
1136                        select_header.cash_rcpt_hist_status,
1137                        select_header.reason_code,
1138                        select_header.bill_to_cust_name,
1139                        select_header.bill_to_cust_no,
1140                        select_header.bill_to_cust_loc,
1141                        select_header.bill_to_cust_addr1,
1142                        select_header.bill_to_cust_addr2,
1143                        select_header.bill_to_cust_addr3,
1144                        select_header.bill_to_cust_addr4,
1145                        select_header.bill_to_cust_city,
1146                        select_header.bill_to_cust_state,
1147                        select_header.bill_to_cust_country,
1148                        select_header.bill_to_cust_zip,
1149                        select_header.ship_to_cust_name,
1150                        select_header.ship_to_cust_no,
1151                        select_header.ship_to_cust_loc,
1152                        select_header.ship_to_cust_addr1,
1153                        select_header.ship_to_cust_addr2,
1154                        select_header.ship_to_cust_addr3,
1155                        select_header.ship_to_cust_addr4,
1156                        select_header.ship_to_cust_city,
1157                        select_header.ship_to_cust_state,
1158                        select_header.ship_to_cust_country,
1159                        select_header.ship_to_cust_zip,
1160                        select_header.remit_to_cust_addr1,
1161                        select_header.remit_to_cust_addr2,
1162                        select_header.remit_to_cust_addr3,
1163                        select_header.remit_to_cust_addr4,
1164                        select_header.remit_to_cust_city,
1165                        select_header.remit_to_cust_state,
1166                        select_header.remit_to_cust_country,
1167                        select_header.remit_to_cust_zip,
1168                        select_header.salesrep_name,
1169                        select_header.term_name,
1170                        select_header.term_due_date,
1171                        select_header.last_printed,
1172                        select_header.printing_option,
1173                        select_header.purchase_order,
1174                        select_header.comments,
1175                        select_header.exch_rate_type,
1176                        select_header.exch_date,
1177                        select_header.exch_rate,
1178                        select_header.curr_code,
1179                        select_header.gl_date,
1180                        select_header.reversal_date,
1181                        select_header.reversal_category,
1182                        select_header.reversal_reason_code,
1183                        select_header.reversal_comments,
1184                        select_header.attr_category,
1185                        select_header.attr1,
1186                        select_header.attr2,
1187                        select_header.attr3,
1188                        select_header.attr4,
1189                        select_header.attr5,
1190                        select_header.attr6,
1191                        select_header.attr7,
1192                        select_header.attr8,
1193                        select_header.attr9,
1194                        select_header.attr10,
1195                        select_header.attr11,
1196                        select_header.attr12,
1197                        select_header.attr13,
1198                        select_header.attr14,
1199                        select_header.attr15,
1200                        select_header.rcpt_method,
1201                        select_header.waybill_no,
1202                        select_header.doc_name,
1203                        select_header.doc_seq_value,
1204                        select_header.st_date_commitment,
1205                        select_header.en_date_commitment,
1206                        select_header.invoicing_rule,
1207                        select_header.bank_acct_name,
1208                        select_header.deposit_date,
1209                        select_header.factor_disc_amount,
1210                        select_header.int_hdr_context,
1211                        select_header.int_hdr_attr1,
1212                        select_header.int_hdr_attr2,
1213                        select_header.int_hdr_attr3,
1214                        select_header.int_hdr_attr4,
1215                        select_header.int_hdr_attr5,
1216                        select_header.int_hdr_attr6,
1217                        select_header.int_hdr_attr7,
1218                        select_header.int_hdr_attr8,
1219                        select_header.int_hdr_attr9,
1220                        select_header.int_hdr_attr10,
1221                        select_header.int_hdr_attr11,
1222                        select_header.int_hdr_attr12,
1223                        select_header.int_hdr_attr13,
1224                        select_header.int_hdr_attr14,
1225                        select_header.int_hdr_attr15,
1226                        select_header.bank_deposit_no,
1227                        select_header.reference_type,
1228                        select_header.reference_id,
1229                        select_header.cust_rcpt_reference,
1230                        select_header.bank_acct_name2
1231                      ) ;
1232 
1233                      -- bug1199027
1234                      l_status := ins_control_detail_table ( NVL(select_header.acctd_amount,0),
1235                                                            select_header.type,
1236                                                            NVL(select_header.open_receivable,'Y'),
1237                                                            l_period_name,
1238                                                            p_archive_id  ) ;
1239 
1240                      IF select_header.type = 'CASH'
1241                      THEN
1242                         l_total_discount := NVL(select_header.acctd_earned_disc_taken,0) +
1243                                                  NVL(select_header.acctd_unearned_disc_taken,0);
1244                         IF l_total_discount IS NOT NULL
1245                         THEN
1246                             -- bug1199027
1247                             l_status := ins_control_detail_table ( l_total_discount,
1248                                                                   'DISC',
1249                                                                   NVL(select_header.open_receivable,'Y'),
1250                                                                   l_period_name,
1251                                                                   p_archive_id  ) ;
1252                         END IF ;
1253                         --
1254                         IF select_header.exch_gain_loss IS NOT NULL
1255                         THEN
1256                             -- bug1199027
1257                             l_status := ins_control_detail_table ( select_header.exch_gain_loss,
1258                                                                   'EXCH',
1259                                                                   NVL(select_header.open_receivable,'Y'),
1260                                                                   l_period_name,
1261                                                                   p_archive_id  ) ;
1262                         END IF ;
1263                      END IF ;
1264 
1265                  EXCEPTION
1266                      WHEN OTHERS THEN
1267                          print( 1, 'Failed while inserting into AR_ARCHIVE_HEADER') ;
1268                          print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
1269                          RAISE ;
1270                  END ;
1271 
1272             END LOOP ;
1273                      FOR select_details IN detail_cursor ( p_cash_receipt_id ,p_archive_level) LOOP
1274              l_account_combination1 := NULL ;
1275              l_account_combination2 := NULL ;
1276              l_account_combination3 := NULL ;
1277              l_account_combination4 := NULL ;
1278              --
1279              IF select_details.ccid1 > 0 THEN
1280                 l_account_combination1 := get_ccid(select_details.ccid1) ;
1281              END IF ;
1282              --
1283              IF select_details.ccid2 > 0 THEN
1284                 l_account_combination2 := get_ccid(select_details.ccid2) ;
1285              END IF ;
1286              --
1287              IF select_details.ccid3 > 0 THEN
1288                 l_account_combination3 := get_ccid(select_details.ccid3) ;
1289              END IF ;
1290              --
1291              IF select_details.ccid4 > 0 THEN
1292                 l_account_combination4 := get_ccid(select_details.ccid4) ;
1293              END IF ;
1294              --
1295              INSERT INTO ar_archive_detail
1296              ( archive_id,
1297                transaction_class,
1298                transaction_type,
1299                transaction_id,
1300                transaction_line_id,
1301                related_transaction_class,
1302                related_transaction_type,
1303                related_transaction_id,
1304                related_transaction_line_id,
1305                line_number,
1306                distribution_type,
1307                application_type,
1308                reason_code_meaning,
1309                line_description,
1310                item_name,
1311                quantity,
1312                unit_selling_price,
1313                line_type,
1314                attribute_category,
1315                attribute1,
1316                attribute2,
1317                attribute3,
1318                attribute4,
1319                attribute5,
1320                attribute6,
1321                attribute7,
1322                attribute8,
1323                attribute9,
1324                attribute10,
1325                attribute11,
1326                attribute12,
1327                attribute13,
1328                attribute14,
1329                attribute15,
1330                amount,
1331                -- acctd_amount, -- bug1199027
1332                uom_code,
1333                ussgl_transaction_code,
1334                tax_rate,
1335                tax_code,
1336                tax_precedence,
1337                account_combination1,
1338                account_combination2,
1339                account_combination3,
1340                account_combination4,
1341                gl_date,
1342                gl_posted_date,
1343                accounting_rule_name,
1344                rule_duration,
1345                rule_start_date,
1346                last_period_to_credit,
1347                comments,
1348                line_adjusted,
1349                freight_adjusted,
1350                tax_adjusted,
1351                receivables_charges_adjusted,
1352                line_applied,
1353                freight_applied,
1354                tax_applied,
1355                receivables_charges_applied,
1356                earned_discount_taken,
1357                unearned_discount_taken,
1358                -- acctd_amount_applied_from, -- bug1199027
1359                -- acctd_amount_applied_to, -- bug1199027
1360                -- acctd_earned_disc_taken, -- bug1199027
1361                -- acctd_unearned_disc_taken, -- bug1199027
1362                factor_discount_amount,
1363                -- acctd_factor_discount_amount, -- bug1199027
1364                interface_line_context,
1365                interface_line_attribute1,
1366                interface_line_attribute2,
1367                interface_line_attribute3,
1368                interface_line_attribute4,
1369                interface_line_attribute5,
1370                interface_line_attribute6,
1371                interface_line_attribute7,
1372                interface_line_attribute8,
1373                interface_line_attribute9,
1374                interface_line_attribute10,
1375                interface_line_attribute11,
1376                interface_line_attribute12,
1377                interface_line_attribute13,
1378                interface_line_attribute14,
1379                interface_line_attribute15,
1380                exchange_rate_type,
1381                exchange_rate_date,
1382                exchange_rate,
1383                due_date,
1384                apply_date,
1385                movement_id,
1386                tax_vendor_return_code,
1387                tax_authority_tax_rates,
1388                tax_exemption_flag,
1389                tax_exemption_id,
1390                tax_exemption_type,
1391                tax_exemption_reason,
1392                tax_exemption_number,
1393                item_exception_rate,
1394                Item_exception_reason
1395              )
1396              VALUES
1397              ( lpad(p_archive_id,14,'0'), /* modified for bug 3266428 */
1398                select_details.trx_class,
1399                select_details.trx_type,
1400                select_details.trx_id,
1401                select_details.line_id,
1402                select_details.related_trx_class,
1403                select_details.related_trx_type,
1404                select_details.related_trx_id,
1405                select_details.related_trx_line_id,
1406                select_details.line_number,
1407                select_details.dist_type,
1408                select_details.app_type,
1409                select_details.line_code_meaning,
1410                select_details.description,
1411                select_details.item_name,
1412                select_details.qty,
1413                select_details.selling_price,
1414                select_details.line_type,
1415                select_details.attr_category,
1416                select_details.attr1,
1417                select_details.attr2,
1418                select_details.attr3,
1419                select_details.attr4,
1420                select_details.attr5,
1421                select_details.attr6,
1422                select_details.attr7,
1423                select_details.attr8,
1424                select_details.attr9,
1425                select_details.attr10,
1426                select_details.attr11,
1427                select_details.attr12,
1428                select_details.attr13,
1429                select_details.attr14,
1430                select_details.attr15,
1431                select_details.amount,
1432                -- select_detail.acctd_amount, -- bug1199027
1433                select_details.uom_code,
1434                select_details.ussgl_trx_code,
1435                select_details.tax_rate,
1436                select_details.tax_code,
1437                select_details.tax_precedence,
1438                l_account_combination1,
1439                l_account_combination2,
1440                l_account_combination3,
1441                l_account_combination4,
1442                select_details.gl_date,
1443                select_details.gl_posted_date,
1444                select_details.rule_name,
1445                select_details.acctg_rule_duration,
1446                select_details.rule_start_date,
1447                select_details.last_period_to_credit,
1448                select_details.line_comment,
1449                select_details.line_adjusted,
1450                select_details.freight_adjusted,
1451                select_details.tax_adjusted,
1452                select_details.charges_adjusted,
1453                select_details.line_applied,
1454                select_details.freight_applied,
1455                select_details.tax_applied,
1456                select_details.charges_applied,
1457                select_details.earned_disc_taken,
1458                select_details.unearned_disc_taken,
1459                -- select_detail.acctd_amount_applied_from, -- bug1199027
1460                -- select_detail.acctd_amount_applied_to, -- bug1199027
1461                -- select_detail.acctd_earned_disc_taken, -- bug1199027
1462                -- select_detail.acctd_unearned_disc_taken, -- bug1199027
1463                select_details.factor_discount_amount,
1464                -- select_detail.acctd_factor_discount_amount, -- bug1199027
1465                select_details.int_line_context,
1466                select_details.int_line_attr1,
1467                select_details.int_line_attr2,
1468                select_details.int_line_attr3,
1469                select_details.int_line_attr4,
1470                select_details.int_line_attr5,
1471                select_details.int_line_attr6,
1472                select_details.int_line_attr7,
1473                select_details.int_line_attr8,
1474                select_details.int_line_attr9,
1475                select_details.int_line_attr10,
1476                select_details.int_line_attr11,
1477                select_details.int_line_attr12,
1478                select_details.int_line_attr13,
1479                select_details.int_line_attr14,
1480                select_details.int_line_attr15,
1481                select_details.exch_rate_type,
1482                select_details.exch_date,
1483                select_details.exch_rate,
1484                select_details.due_date,
1485                select_details.apply_date,
1486                select_details.movement_id,
1487                select_details.vendor_return_code,
1488                select_details.tax_auth_tax_rate,
1489                select_details.tax_exempt_flag,
1490                select_details.tax_exemption_id,
1491                select_details.exemption_type,
1492                select_details.tax_exemption_reason,
1493                select_details.tax_exemption_number,
1494                select_details.item_exception_rate,
1495                select_details.meaning
1496              ) ;
1497 
1498          END LOOP ;
1499 
1500             RETURN ( TRUE );
1501 
1502         EXCEPTION
1503             WHEN OTHERS THEN
1504                 print( 1, '  ...Failed while inserting into AR_ARCHIVE_HEADER');
1505                 print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
1506                 RAISE ;
1507         END ;
1508     END ;
1509 
1510     --
1511     --
1512     -- Insert into AR_ARCHIVE_HEADER
1513     --
1514     FUNCTION archive_header( p_customer_trx_id IN NUMBER ,
1515                              p_archive_id      IN NUMBER) RETURN BOOLEAN IS
1516     BEGIN
1517     DECLARE
1518         CURSOR header_cursor ( cp_customer_trx_id NUMBER ) IS
1519         SELECT ctt.type  type,      /* transaction_class */
1520                ctt.name  name,      /* transaction_type */
1521                ct.customer_trx_id  trx_id,   /* transaction_id */
1522                decode(ctt.type, 'CM', ctt_prev.type)
1523                    related_trx_type,            /* related_transaction_class */
1524                decode(ctt.type, 'CM', ctt_prev.name)
1525                    related_trx_id,              /* related_transaction_type */
1526                decode(ctt.type, 'CM', ct.previous_customer_trx_id)
1527                    prev_trx_id ,                /* related_transaction_id */
1528                ct.trx_number trx_number,        /* transaction_number */
1529                ct.trx_date   trx_date,          /* transaction_date */
1530                batch.name    batch_name,
1531                bs.name       batch_source_name,
1532                sob.name      sob_name,
1533                ctlgd.amount  amount,
1534                ctlgd.acctd_amount acctd_amount,
1535                to_number('') exch_gain_loss,        /* exchange_gain_loss */
1536                to_number('') earned_disc_taken,        /* earned_discount_taken */
1537                to_number('') unearned_disc_taken,     /* unearned_discount_taken */
1538                to_number('') acctd_earned_disc_taken, /* acctd_earned_discount_taken */
1539                to_number('') acctd_unearned_disc_taken,   /* acctd_unearned_discount_taken */
1540                '' adj_trx_type,        /* type */
1541                '' adj_type,        /* adjustment_type */
1542                ctt.post_to_gl post_to_gl,
1543                ctt.accounting_affect_flag open_receivable,
1544                '' cash_rcpt_status,    /* cash_receipt_status */
1545                '' cash_rcpt_hist_status,  /* cash_receipt_history_status */
1546                lu.meaning reason_code,     /* reason_code_meaning */
1547                substrb(bill_party.party_name,1,50)  bill_to_cust_name,
1548                cust_bill.account_number bill_to_cust_no,
1549                su_bill.location bill_to_cust_loc,
1550                bill_loc.address1 bill_to_cust_addr1,
1551                bill_loc.address2 bill_to_cust_addr2,
1552                bill_loc.address3 bill_to_cust_addr3,
1553                bill_loc.address4 bill_to_cust_addr4,
1554                bill_loc.city bill_to_cust_city,
1555                bill_loc.state bill_to_cust_state,
1556                bill_loc.country bill_to_cust_country,
1557                bill_loc.postal_code bill_to_cust_zip,
1558                substrb(ship_party.party_name,1,50) ship_to_cust_name,
1559                cust_ship.account_number ship_to_cust_no,
1560                su_ship.location      ship_to_cust_loc,
1561                ship_loc.address1    ship_to_cust_addr1,
1562                ship_loc.address2    ship_to_cust_addr2,
1563                ship_loc.address3    ship_to_cust_addr3,
1564                ship_loc.address4    ship_to_cust_addr4,
1565                ship_loc.city        ship_to_cust_city,
1566                ship_loc.state       ship_to_cust_state,
1567                ship_loc.country     ship_to_cust_country,
1568                ship_loc.postal_code ship_to_cust_zip,
1569                remit_loc.address1   remit_to_cust_addr1,
1570                remit_loc.address2   remit_to_cust_addr2,
1571                remit_loc.address3   remit_to_cust_addr3,
1572                remit_loc.address4   remit_to_cust_addr4,
1573                remit_loc.city       remit_to_cust_city,
1574                remit_loc.state      remit_to_cust_state,
1575                remit_loc.country    remit_to_cust_country,
1576                remit_loc.postal_code remit_to_cust_zip,
1577                sales.name             salesrep_name,
1578                term.name              term_name,
1579                ct.term_due_date       term_due_date,
1580                ct.printing_last_printed last_printed,
1581                ct.printing_option printing_option,
1582                ct.purchase_order purchase_order,
1583                ct.comments            comments,
1584                ct.exchange_rate_type exch_rate_type,
1585                ct.exchange_date exch_date,
1586                ct.exchange_rate exch_rate,
1587                ct.invoice_currency_code curr_code,
1588                nvl(ctlgd.gl_date, ct.trx_date) gl_date,
1589                to_date(NULL) reversal_date,  /* reversal_date */
1590                '' reversal_category,    /* reversal_category */
1591                '' reversal_reason_code,    /* reversal_reason_code_meaning */
1592                '' reversal_comments,     /* reversal_comments */
1593                ct.attribute_category attr_category,
1594                ct.attribute1 attr1,
1595                ct.attribute2 attr2,
1596                ct.attribute3 attr3,
1597                ct.attribute4 attr4,
1598                ct.attribute5 attr5,
1599                ct.attribute6 attr6,
1600                ct.attribute7 attr7,
1601                ct.attribute8 attr8,
1602                ct.attribute9 attr9,
1603                ct.attribute10 attr10,
1604                ct.attribute11 attr11,
1605                ct.attribute12 attr12,
1606                ct.attribute13 attr13,
1607                ct.attribute14 attr14,
1608                ct.attribute15 attr15,
1609                '' rcpt_method,             /* receipt_method_name */
1610                ct.waybill_number waybill_no,
1611                doc.name doc_name,
1612                ct.doc_sequence_value doc_seq_value,
1613                ct.start_date_commitment st_date_commitment,
1614                ct.end_date_commitment en_date_commitment,
1615                rule.name invoicing_rule,
1616                '' bank_acct_name,
1617                to_date(NULL) deposit_date,  /* deposit_date */
1618                to_number('') factor_disc_amount,/* factor_discount_amount */
1619                ct.interface_header_context     int_hdr_context,
1620                ct.interface_header_attribute1  int_hdr_attr1,
1621                ct.interface_header_attribute2  int_hdr_attr2,
1622                ct.interface_header_attribute3  int_hdr_attr3,
1623                ct.interface_header_attribute4  int_hdr_attr4,
1624                ct.interface_header_attribute5  int_hdr_attr5,
1625                ct.interface_header_attribute6  int_hdr_attr6,
1626                ct.interface_header_attribute7  int_hdr_attr7,
1627                ct.interface_header_attribute8  int_hdr_attr8,
1628                ct.interface_header_attribute9  int_hdr_attr9,
1629                ct.interface_header_attribute10 int_hdr_attr10,
1630                ct.interface_header_attribute11 int_hdr_attr11,
1631                ct.interface_header_attribute12 int_hdr_attr12,
1632                ct.interface_header_attribute13 int_hdr_attr13,
1633                ct.interface_header_attribute14 int_hdr_attr14,
1634                ct.interface_header_attribute15 int_hdr_attr15,
1635                '' bank_deposit_no,           /* bank_deposit_number */
1636                '' reference_type,            /* reference_type */
1637                to_number('') reference_id,   /* reference_id */
1638                '' cust_rcpt_reference,       /* customer_receipt_reference */
1639                '' bank_acct_name2 /* bank_account_name */
1640         FROM   ar_lookups        lu,
1641                ra_rules          rule,
1642                ra_cust_trx_types ctt_prev,
1643                ra_cust_trx_types ctt,
1644                ra_batch_sources  bs,
1645                ra_batches        batch,
1646                fnd_document_sequences doc,
1647                gl_sets_of_books  sob,
1648                hz_cust_accounts  cust_bill,
1649                hz_parties        bill_party,
1650                hz_cust_site_uses su_bill,
1651                hz_cust_acct_sites addr_bill,
1652                hz_party_sites     bill_ps,
1653                hz_locations       bill_loc,
1654                hz_cust_accounts  cust_ship,
1655                hz_parties        ship_party,
1656                hz_cust_site_uses su_ship,
1657                hz_cust_acct_sites addr_ship,
1658                hz_party_sites     ship_ps,
1659                hz_locations       ship_loc,
1660                hz_cust_acct_sites addr_remit,
1661                hz_party_sites     remit_ps,
1662                hz_locations       remit_loc,
1663                iby_trxn_extensions_v iby,
1664                ra_salesreps      sales,
1665                ra_terms          term,
1666                ra_cust_trx_line_gl_dist ctlgd,
1667                ra_customer_trx   ct_prev,
1668                ra_customer_trx   ct
1669         WHERE  lu.lookup_code (+) = ct.reason_code
1670         AND    lu.lookup_type (+) = 'INVOICING_REASON'
1671         AND    iby.trxn_extension_id(+)     = ct.payment_trxn_extension_id
1672         AND    rule.rule_id (+)             = ct.invoicing_rule_id
1673         AND    ctt.cust_trx_type_id         = ct.cust_trx_type_id
1674         AND    bs.batch_source_id           = ct.batch_source_id
1675         AND    batch.batch_id (+)           = ct.batch_id
1676         AND    doc.doc_sequence_id (+)      = ct.doc_sequence_id
1677         AND    sob.set_of_books_id          = ct.set_of_books_id
1678         AND    cust_bill.cust_account_id (+) = ct.bill_to_customer_id
1679         AND    cust_bill.party_id           = bill_party.party_id(+)
1680         AND    su_bill.site_use_id (+)      = ct.bill_to_site_use_id
1681         AND    addr_bill.cust_acct_site_id (+) = su_bill.cust_acct_site_id
1682         AND    addr_bill.party_site_id      = bill_ps.party_site_id(+)
1683         AND    bill_loc.location_id(+)      = bill_ps.location_id
1684         AND    cust_ship.cust_account_id(+) = ct.ship_to_customer_id
1685         AND    cust_ship.party_id           = ship_party.party_id(+)
1686         AND    su_ship.site_use_id (+)      = ct.ship_to_site_use_id
1687         AND    addr_ship.cust_acct_site_id (+) = su_ship.cust_acct_site_id
1688         AND    addr_ship.party_site_id      = ship_ps.party_site_id(+)
1689         AND    ship_loc.location_id (+)        = ship_ps.location_id
1690         AND    addr_remit.cust_acct_site_id (+) = ct.remit_to_address_id
1691         AND    addr_remit.party_site_id     = remit_ps.party_site_id(+)
1692         AND    remit_loc.location_id(+)        = remit_ps.location_id
1693         AND    sales.salesrep_id(+)         = ct.primary_salesrep_id
1694         AND    term.term_id (+)             = ct.term_id
1695         AND    ctlgd.customer_trx_id        = ct.customer_trx_id
1696         AND    ctlgd.account_class          = 'REC'
1697         AND    ctlgd.latest_rec_flag        = 'Y'
1698         AND    ct.previous_customer_trx_id  = ct_prev.customer_trx_id(+)
1699         AND    ct_prev.cust_trx_type_id     = ctt_prev.cust_trx_type_id(+)
1700         AND    ct.customer_trx_id           = cp_customer_trx_id
1701         UNION
1702         --------------------------------------------------------------------
1703         -- ADJ: adjustments
1704         --------------------------------------------------------------------
1705         SELECT 'ADJ'  type,        /* transaction_class */
1706                ''     name,                       /* transaction_type */
1707                adj.adjustment_id  trx_id,         /* transaction_id */
1708                ctt.type  related_trx_type,    /* related_transaction_class */
1709                ctt.name  related_trx_id,    /* related_transaction_type */
1710                ct.customer_trx_id prev_trx_id,    /* related_transaction_id */
1711                adj.adjustment_number trx_number,  /* transaction_number */
1712                adj.apply_date trx_date,      /* transaction_date */
1713                ''  batch_name,        /* batch_name */
1714                ''  batch_source_name,       /* batch_source_name */
1715                sob.name  sob_name,
1716                adj.amount amount,
1717                adj.acctd_amount acctd_amount,
1718                to_number('') exch_gain_loss,          /* exchange_gain_loss */
1719                to_number('') earned_disc_taken,    /* earned_discount_taken */
1720                to_number('') unearned_disc_taken,  /* unearned_discount_taken */
1721                to_number('') acctd_earned_disc_taken,   /* acctd_earned_discount_taken */
1722                to_number('') acctd_unearned_disc_taken,  /* acctd_unearned_discount_taken */
1723                adj.type  adj_trx_type,
1724                adj.adjustment_type adj_type,
1725                '' post_to_gl,            /* post_to_gl */
1726                '' open_receivable,    /* accounting_affect_flag */
1727                '' cash_rcpt_status,          /* cash_receipt_status */
1728                '' cash_rcpt_hist_status,  /* cash_receipt_history_status */
1729                lu.meaning reason_code,      /* reason_code_meaning */
1730                substrb(cust_party.party_name,1,50)  bill_to_cust_name,  /* bill_to_customer_name */
1731                cust.account_number bill_to_cust_no,  /* bill_to_customer_number */
1732                '' bill_to_cust_loc,    /* bill_to_customer_location */
1733                '' bill_to_cust_addr1,    /* bill_to_customer_address1 */
1734                '' bill_to_cust_addr2,    /* bill_to_customer_address2 */
1735                '' bill_to_cust_addr3,    /* bill_to_customer_address3 */
1736                '' bill_to_cust_addr4,    /* bill_to_customer_address4 */
1737                '' bill_to_cust_city,    /* bill_to_customer_city */
1738                '' bill_to_cust_state,    /* bill_to_customer_state */
1739                '' bill_to_cust_country,    /* bill_to_customer_country */
1740                '' bill_to_cust_zip,    /* bill_to_customer_postal_code */
1741                '' ship_to_cust_name,    /* ship_to_customer_name */
1742                '' ship_to_cust_no,    /* ship_to_customer_number */
1743                '' ship_to_cust_loc,    /* ship_to_customer_location */
1744                '' ship_to_cust_addr1,           /* ship_to_customer_address1 */
1745                '' ship_to_cust_addr2,           /* ship_to_customer_address2 */
1746                '' ship_to_cust_addr3,    /* ship_to_customer_address3 */
1747                '' ship_to_cust_addr4,    /* ship_to_customer_address4 */
1748                '' ship_to_cust_city,    /* ship_to_customer_city */
1749                '' ship_to_cust_state,           /* ship_to_customer_state */
1750                '' ship_to_cust_country,         /* ship_to_customer_country */
1751                '' ship_to_cust_zip,    /* ship_to_customer_postal_code */
1752                '' remit_to_cust_addr1,    /* remit_to_customer_address1 */
1753                '' remit_to_cust_addr2,          /* remit_to_customer_address2 */
1754                '' remit_to_cust_addr3,          /* remit_to_customer_address3 */
1755                '' remit_to_cust_addr4,          /* remit_to_customer_address4 */
1756                '' remit_to_cust_city,           /* remit_to_customer_city */
1757                '' remit_to_cust_state,          /* remit_to_customer_state */
1758                '' remit_to_cust_country,        /* remit_to_customer_country */
1759                '' remit_to_cust_zip,          /* remit_to_customer_postal_code */
1760                '' salesrep_name,    /* salesrep_name */
1761                '' term_name,             /* term_name */
1762                to_date(NULL) term_due_date,       /* term_due_date */
1763                to_date(NULL) last_printed,        /* printing_last_printed */
1764                '' printing_option,          /* printing_option */
1765                '' purchase_order,     /* purchase_order */
1766                '' comments,               /* comments */
1767                '' exch_rate_type,    /* exchange_rate_type */
1768                to_date(NULL) exch_date,   /* exchange_rate_date */
1769                to_number('') exch_rate,   /* exchange_rate */
1770                ct.invoice_currency_code curr_code,
1771                nvl(adj.gl_date, ct.trx_date)  gl_date,
1772                to_date(NULL) reversal_date,    /* reversal_date */
1773                '' reversal_catergory,      /* reversal_category */
1774                '' reversal_reason_code,      /* reversal_reason_code_meaning */
1775                '' reversal_comments,       /* reversal_comments */
1776                adj.attribute_category attr_catergory,
1777                adj.attribute1 attr1,
1778                adj.attribute2 attr2,
1779                adj.attribute3 attr3,
1780                adj.attribute4 attr4,
1781                adj.attribute5 attr5,
1782                adj.attribute6 attr6,
1783                adj.attribute7 attr7,
1784                adj.attribute8 attr8,
1785                adj.attribute9 attr9,
1786                adj.attribute10 attr10,
1787                adj.attribute11 attr11,
1788                adj.attribute12 attr12,
1789                adj.attribute13 attr13,
1790                adj.attribute14 attr14,
1791                adj.attribute15 attr15,
1792                '' rcpt_method,     /* receipt_method_name */
1793                '' waybill_no,      /* waybill_number */
1794                doc.name doc_name,
1795                adj.doc_sequence_value doc_seq_value,
1796                to_date(NULL) st_date_commitment,    /* start_date_commitment */
1797                to_date(NULL) en_date_commitment,    /* end_date_commitment */
1798                '' invoicing_rule,      /* invoicing_rule_name */
1799                '' bank_acct_name,      /* bank_account_name */
1800                to_date(NULL) deposit_date,    /* deposit_date */
1801                to_number('') factor_disc_amount,/* factor_discount_amount */
1802                '' int_hdr_context,    /* interface_header_context */
1803                '' int_hdr_attr1,    /* interface_header_attribute1 */
1804                '' int_hdr_attr2,    /* interface_header_attribute2 */
1805                '' int_hdr_attr3,    /* interface_header_attribute3 */
1806                '' int_hdr_attr4,    /* interface_header_attribute4 */
1807                '' int_hdr_attr5,    /* interface_header_attribute5 */
1808                '' int_hdr_attr6,    /* interface_header_attribute6 */
1809                '' int_hdr_attr7,    /* interface_header_attribute7 */
1810                '' int_hdr_attr8,    /* interface_header_attribute8 */
1811                '' int_hdr_attr9,    /* interface_header_attribute9 */
1812                '' int_hdr_attr10,    /* interface_header_attribute10 */
1813                '' int_hdr_attr11,    /* interface_header_attribute11 */
1814                '' int_hdr_attr12,    /* interface_header_attribute12 */
1815                '' int_hdr_attr13,    /* interface_header_attribute13 */
1816                '' int_hdr_attr14,    /* interface_header_attribute14 */
1817                '' int_hdr_attr15,    /* interface_header_attribute15 */
1818                '' bank_deposit_no,    /* bank_deposit_number */
1819                '' reference_type,    /* reference_type */
1820                to_number('') reference_id,  /* reference_id */
1821                '' cust_rcpt_reference,    /* customer_receipt_reference */
1822                '' bank_acct_name2               /* bank_account_name */
1823         FROM   ra_cust_trx_types ctt,
1824                fnd_document_sequences doc,
1825                gl_sets_of_books  sob,
1826                ar_lookups        lu,
1827                ar_adjustments    adj,
1828                hz_cust_accounts  cust,
1829                hz_parties        cust_party,
1830                ra_customer_trx   ct
1831         WHERE  lu.lookup_code (+)      = adj.reason_code
1832         AND    lu.lookup_type (+)      = 'ADJUST_REASON'
1833         AND    ctt.cust_trx_type_id    = ct.cust_trx_type_id
1834         AND    doc.doc_sequence_id (+) = adj.doc_sequence_id
1835         AND    sob.set_of_books_id     = adj.set_of_books_id
1836         AND    adj.customer_trx_id     = ct.customer_trx_id
1837                /* do not archive unaccrued adjustments */
1838         AND    adj.status <> 'U'
1839         AND    cust.cust_account_id (+)    = ct.bill_to_customer_id
1840         AND    cust.party_id = cust_party.party_id (+)
1841         AND    ct.customer_trx_id      = cp_customer_trx_id
1842         UNION
1843         --------------------------------------------------------------------
1844         -- REC: cash receipts
1845         --------------------------------------------------------------------
1846         SELECT cr.type type,      /* transaction_class */
1847                '' name,              /* transaction_type */
1848                cr.cash_receipt_id trx_id,   /* transaction_id */
1849                '' related_trx_type,    /* related_transaction_class */
1850                '' related_trx_id,    /* related_transaction_type */
1851                to_number('') prev_trx_id,   /* related_transaction_id */
1852                cr.receipt_number trx_number,  /* transaction_number */
1853                cr.receipt_date trx_date,  /* transaction_date */
1854                batch.name batch_name,
1855                bs.name    batch_source_name,
1856                sob.name   sob_name,
1857                cr.amount  amount,
1858                -- bug1199027
1859                sum( ra.acctd_amount_applied_to ) acctd_amount,/* acctd_amount */
1860                sum( ra.acctd_amount_applied_from - ra.acctd_amount_applied_to )
1861                         exch_gain_loss, /* exchange_gain_loss */
1862                sum( ra.earned_discount_taken ) earned_disc_taken ,
1863                sum( ra.unearned_discount_taken ) unearned_disc_taken ,
1864                sum( ra.acctd_earned_discount_taken ) acctd_earned_disc_taken ,
1865                sum( ra.acctd_unearned_discount_taken ) acctd_unearned_disc_taken ,
1866                cr.type adj_trx_type,
1867                '' adj_type,      /* adjustment_type */
1868                ''  post_to_gl,                  /* post_to_gl */
1869                ''  open_receivable,             /* accounting_affect_flag */
1870                cr.status cash_rcpt_status,  /* cash_receipt_status */
1871                crh.status cash_rcpt_hist_status,/* cash_receipt_history_status */
1872                '' reason_code,                 /* reason_code_meaning */
1873                substrb(cust_party.party_name,1,50)  bill_to_cust_name,    /* bill_to_customer_name */
1874                cust.account_number bill_to_cust_no,          /* bill_to_customer_number */
1875                su.location bill_to_cust_loc,      /* bill_to_customer_location */
1876                substrb(loc.address1, 1, 80) bill_to_cust_addr1, /* bill_to_customer_address1 */
1877                substrb(loc.address2, 1, 80) bill_to_cust_addr2, /* bill_to_customer_address2 */
1878                substrb(loc.address3, 1, 80) bill_to_cust_addr3, /* bill_to_customer_address3 */
1879                substrb(loc.address4, 1, 80) bill_to_cust_addr4, /* bill_to_customer_address4 */
1880                loc.city  bill_to_cust_city,      /* bill_to_customer_city */
1881                loc.state bill_to_cust_state,      /* bill_to_customer_state */
1882                loc.country bill_to_cust_country,               /* bill_to_customer_country */
1883                loc.postal_code bill_to_cust_zip,    /* bill_to_postal_code*/
1884                '' ship_to_cust_name,    /* ship_to_customer_name */
1885                '' ship_to_cust_no,     /* ship_to_customer_number */
1886                '' ship_to_cust_loc,     /* ship_to_customer_location */
1887                '' ship_to_cust_addr1,     /* ship_to_customer_address1 */
1888                '' ship_to_cust_addr2,     /* ship_to_customer_address2 */
1889                '' ship_to_cust_addr3,    /* ship_to_customer_address3 */
1890                '' ship_to_cust_addr4,     /* ship_to_customer_address4 */
1891                '' ship_to_cust_city,     /* ship_to_customer_city */
1892                '' ship_to_cust_state,     /* ship_to_customer_state */
1893                '' ship_to_cust_country,   /* ship_to_customer_country */
1894                '' ship_to_cust_zip,    /* ship_to_customer_postal_code */
1895                '' remit_to_cust_addr1,    /* remit_to_customer_address1 */
1896                '' remit_to_cust_addr2,    /* remit_to_customer_address2 */
1897                '' remit_to_cust_addr3,    /* remit_to_customer_address3 */
1898                '' remit_to_cust_addr4,    /* remit_to_customer_address4 */
1899                '' remit_to_cust_city,     /* remit_to_customer_city */
1900                '' remit_to_cust_state,     /* remit_to_customer_state */
1901                '' remit_to_cust_country,   /* remit_to_customer_country */
1902                '' remit_to_cust_zip,     /* remit_to_customer_postal_code */
1903                '' salesrep_name,     /* salesrep_name */
1904                '' term_name,       /* term_name */
1905                to_date(NULL) term_due_date,  /* term_due_date */
1906                to_date(NULL) last_printed,  /* printing_last_printed */
1907                '' printing_option,      /* printing_option */
1908                '' purchase_order,      /* purchase_order */
1909                cr.comments comments,
1910                cr.exchange_rate_type exch_rate_type,
1911                cr.exchange_date exch_date,
1912                cr.exchange_rate exch_rate,
1913                cr.currency_code curr_code,
1914                nvl(crh.gl_date, cr.receipt_date) gl_date,
1915                cr.reversal_date reversal_date,
1916                substrb(lu1.meaning, 1, 20) reversal_category,   /* reversal_category */
1917                lu2.meaning reversal_reason_code,           /* reversal_reason_code_meaning */
1918                cr.reversal_comments reversal_comments,
1919                substrb(cr.attribute_category, 1, 30) attr_category,
1920                cr.attribute1 attr1,
1921                cr.attribute2 attr2,
1922                cr.attribute3 attr3,
1923                cr.attribute4 attr4,
1924                cr.attribute5 attr5,
1925                cr.attribute6 attr6,
1926                cr.attribute7 attr7,
1927                cr.attribute8 attr8,
1928                cr.attribute9 attr9,
1929                cr.attribute10 attr10,
1930                cr.attribute11 attr11,
1931                cr.attribute12 attr12,
1932                cr.attribute13 attr13,
1933                cr.attribute14 attr14,
1934                cr.attribute15 attr15,
1935                rm.name rcpt_method,    /* receipt_method_name */
1936                '' waybill_no,      /* waybill_number */
1937                doc.name doc_name,
1938                cr.doc_sequence_value doc_seq_value,
1939                to_date(NULL) st_date_commitment,    /* start_date_commitment */
1940                to_date(NULL) en_date_commitment,    /* end_date_commitment */
1941                '' invoicing_rule,       /* invoicing_rule_name */
1942                '' bank_acct_name,
1943                cr.deposit_date deposit_date,
1944                cr.factor_discount_amount factor_disc_amount,
1945                '' int_hdr_context,      /* interface_header_context */
1946                '' int_hdr_attr1,        /* interface_header_attribute1 */
1947                '' int_hdr_attr2,  /* interface_header_attribute2 */
1948                '' int_hdr_attr3,  /* interface_header_attribute3 */
1949                '' int_hdr_attr4,  /* interface_header_attribute4 */
1950                '' int_hdr_attr5,  /* interface_header_attribute5 */
1951                '' int_hdr_attr6,  /* interface_header_attribute6 */
1952                '' int_hdr_attr7,  /* interface_header_attribute7 */
1953                '' int_hdr_attr8,  /* interface_header_attribute8 */
1954                '' int_hdr_attr9,  /* interface_header_attribute9 */
1955                '' int_hdr_attr10,  /* interface_header_attribute10 */
1956                '' int_hdr_attr11,  /* interface_header_attribute11 */
1957                '' int_hdr_attr12,  /* interface_header_attribute12 */
1958                '' int_hdr_attr13,  /* interface_header_attribute13 */
1959                '' int_hdr_attr14,  /* interface_header_attribute14 */
1960                '' int_hdr_attr15,   /* interface_header_attribute15 */
1961                batch_remit.bank_deposit_number bank_deposit_no,
1962                cr.reference_type reference_type,
1963                cr.reference_id reference_id,
1964                cr.customer_receipt_reference cust_rcpt_reference,
1965                cba.bank_account_name bank_acct_name2
1966         FROM   ar_lookups lu1,
1967                ar_lookups lu2,
1968                ar_receipt_methods rm,
1969                ar_batch_sources  bs,
1970                ar_batches        batch,
1971                ar_batches        batch_remit,
1972                ce_bank_accounts  cba,
1973                ce_bank_acct_uses ba2,
1974                ce_bank_branches_v bb,
1975                fnd_document_sequences doc,
1976                gl_sets_of_books  sob,
1977                hz_cust_acct_sites addr,
1978                hz_party_sites     party_site,
1979                hz_locations       loc,
1980                hz_cust_site_uses su,
1981                hz_cust_accounts  cust,
1982                hz_parties        cust_party,
1983                iby_trxn_extensions_v iby,
1984                ar_receivable_applications ra,
1985                ar_receivable_applications ra1, --bug1199027
1986                ar_cash_receipt_history crh,
1987                ar_cash_receipt_history crh_batch,
1988                ar_cash_receipt_history crh_remit,
1989                ar_cash_receipts  cr
1990         WHERE  lu1.lookup_code (+)  = cr.reversal_category
1991         AND    lu1.lookup_type (+)  = 'REVERSAL_CATEGORY_TYPE'
1992         AND    lu2.lookup_code (+)  = cr.reversal_reason_code
1993         AND    lu2.lookup_type (+)  = 'CKAJST_REASON'
1994         AND    iby.trxn_extension_id(+)     = cr.payment_trxn_extension_id
1995         AND    ba2.bank_account_id          = cba.bank_account_id (+)
1996         AND    ba2.bank_acct_use_id (+)     = cr.remit_bank_acct_use_id
1997         AND    bb.branch_party_id  (+)      = cba.bank_branch_id
1998         AND    rm.receipt_method_id (+)     = cr.receipt_method_id
1999         AND    cust.cust_account_id (+)     = cr.pay_from_customer
2000         AND    cust.party_id                = cust_party.party_id(+)
2001         AND    su.site_use_id (+)           = cr.customer_site_use_id
2002         AND    addr.cust_acct_site_id (+)   = su.cust_acct_site_id
2003         AND    addr.party_site_id           = party_site.party_site_id(+)
2004         AND    loc.location_id (+)          = party_site.location_id
2005         AND    doc.doc_sequence_id (+)      = cr.doc_sequence_id
2006         AND    sob.set_of_books_id          = cr.set_of_books_id
2007                /* get CR batch info */
2008         AND    bs.batch_source_id (+)       = batch.batch_source_id
2009         AND    batch.batch_id (+)           = crh_batch.batch_id
2010         AND    crh_batch.first_posted_record_flag = 'Y'
2011         AND    crh_batch.cash_receipt_id    = cr.cash_receipt_id
2012                /* get current crh record for gl_date */
2013         AND    crh.cash_receipt_id          = cr.cash_receipt_id
2014         AND    crh.current_record_flag      = 'Y'
2015                /* get remittance batch */
2016         AND    crh_remit.batch_id           = batch_remit.batch_id(+)
2017         AND    nvl(crh_remit.cash_receipt_history_id, -99) in
2018                    ( SELECT nvl( min(crh1.cash_receipt_history_id), -99 )
2019                      from   ar_cash_receipt_history crh1
2020                      where  crh1.cash_receipt_id  = cr.cash_receipt_id
2021                      and    crh1.status = 'REMITTED' )
2022         AND    crh_remit.status (+)         = 'REMITTED'
2023         AND    crh_remit.cash_receipt_id(+) = cr.cash_receipt_id
2024         AND    cr.cash_receipt_id           = ra.cash_receipt_id
2025         -- bug1199027
2026         and    ra.cash_receipt_id           = ra1.cash_receipt_id
2027         and    ra.status = ra1.status
2028         and    ra1.applied_customer_trx_id  = cp_customer_trx_id
2029         and    ra1.status = 'APP'
2030         -- bug2859402 Don't insert duplicate cash record.
2031         and    not exists (
2032                   select 'already purged'
2033                     from ar_archive_header aah
2034                    where aah.transaction_id = cr.cash_receipt_id
2035                      and aah.transaction_class = 'CASH' )
2036         GROUP BY cr.type,      /* transaction_class */
2037                  cr.cash_receipt_id,     /* transaction_id */
2038                  cr.receipt_number,    /* transaction_number */
2039                  cr.receipt_date,    /* transaction_date */
2040                  batch.name,
2041                  bs.name,
2042                  sob.name,
2043                  cr.amount,
2044                  cr.type,
2045                  cr.status,      /* cash_receipt_status */
2046                  crh.status,      /* cash_receipt_history_status */
2047                  cust_party.party_name,    /* bill_to_customer_name */
2048                  cust.account_number,    /* bill_to_customer_number */
2049                  su.location,      /* bill_to_customer_location */
2050                  substrb(loc.address1, 1, 80),   /* bill_to_customer_address1 */
2051                  substrb(loc.address2, 1, 80),  /* bill_to_customer_address2 */
2052                  substrb(loc.address3, 1, 80),   /* bill_to_customer_address3 */
2053                  substrb(loc.address4, 1, 80),   /* bill_to_customer_address4 */
2054                  loc.city,      /* bill_to_customer_city */
2055                  loc.state,      /* bill_to_customer_state */
2056                  loc.country,      /* bill_to_customer_country */
2057                  loc.postal_code,    /* bill_to_customer_postal_code */
2058                  cr.comments,
2059                  cr.exchange_rate_type,
2060                  cr.exchange_date,
2061                  cr.exchange_rate,
2062                  cr.currency_code,
2063                  nvl(crh.gl_date, cr.receipt_date),
2064                  cr.reversal_date,
2065                  substrb(lu1.meaning, 1, 20),   /* reversal_category */
2066                  lu2.meaning,           /* reversal_reason_code_meaning */
2067                  cr.reversal_comments,
2068                  substrb(cr.attribute_category, 1, 30),
2069                  cr.attribute1,
2070                  cr.attribute2,
2071                  cr.attribute3,
2072                  cr.attribute4,
2073                  cr.attribute5,
2074                  cr.attribute6,
2075                  cr.attribute7,
2076                  cr.attribute8,
2077                  cr.attribute9,
2078                  cr.attribute10,
2079                  cr.attribute11,
2080                  cr.attribute12,
2081                  cr.attribute13,
2082                  cr.attribute14,
2083                  cr.attribute15,
2084                  rm.name,      /* receipt_method_name */
2085                  doc.name,
2086                  cr.doc_sequence_value,
2087                  cr.deposit_date,
2088                  cr.factor_discount_amount,
2089                  batch_remit.bank_deposit_number,
2090                  cr.reference_type,
2091                  cr.reference_id,
2092                  cr.customer_receipt_reference,
2093                  cba.bank_account_name  ;
2094         l_total_discount  NUMBER ;
2095         l_period_name     VARCHAR2(15) ;
2096         l_status          BOOLEAN ;
2097 
2098         BEGIN
2099 
2100             FOR select_header IN header_cursor ( p_customer_trx_id )
2101             LOOP
2102             -- Collect Statistics
2103 
2104                  l_period_name := get_period_name ( select_header.gl_date ) ;
2105 
2106                  BEGIN
2107 
2108                      INSERT INTO ar_archive_header
2109                      ( archive_id,
2110                        transaction_class,
2111                        transaction_type,
2112                        transaction_id,
2113                        related_transaction_class,
2114                        related_transaction_type,
2115                        related_transaction_id,
2116                        transaction_number,
2117                        transaction_date,
2118                        batch_name,
2119                        batch_source_name,
2120                        set_of_books_name,
2121                        amount,
2122                        -- acctd_amount, -- bug1199027
2123                        exchange_gain_loss,
2124                        earned_discount_taken,
2125                        unearned_discount_taken,
2126                        -- acctd_earned_discount_taken, -- bug1199027
2127                        -- acctd_unearned_discount_taken, -- bug1199027
2128                        type,
2129                        adjustment_type,
2130                        post_to_gl,
2131                        accounting_affect_flag,
2132                        cash_receipt_status,
2133                        cash_receipt_history_status,
2134                        reason_code_meaning,
2135                        bill_to_customer_name,
2136                        bill_to_customer_number,
2137                        bill_to_customer_location,
2138                        bill_to_customer_address1,
2139                        bill_to_customer_address2,
2140                        bill_to_customer_address3,
2141                        bill_to_customer_address4,
2142                        bill_to_customer_city,
2143                        bill_to_customer_state,
2144                        bill_to_customer_country,
2145                        bill_to_customer_postal_code,
2146                        ship_to_customer_name,
2147                        ship_to_customer_number,
2148                        ship_to_customer_location,
2149                        ship_to_customer_address1,
2150                        ship_to_customer_address2,
2151                        ship_to_customer_address3,
2152                        ship_to_customer_address4,
2153                        ship_to_customer_city,
2154                        ship_to_customer_state,
2155                        ship_to_customer_country,
2156                        ship_to_customer_postal_code,
2157                        remit_to_address1,
2158                        remit_to_address2,
2159                        remit_to_address3,
2160                        remit_to_address4,
2161                        remit_to_city,
2162                        remit_to_state,
2163                        remit_to_country,
2164                        remit_to_postal_code,
2165                        salesrep_name,
2166                        term_name,
2167                        term_due_date,
2168                        printing_last_printed,
2169                        printing_option,
2170                        purchase_order,
2171                        comments,
2172                        exchange_rate_type,
2173                        exchange_rate_date,
2174                        exchange_rate,
2175                        currency_code,
2176                        gl_date,
2177                        reversal_date,
2178                        reversal_category,
2179                        reversal_reason_code_meaning,
2180                        reversal_comments,
2181                        attribute_category,
2182                        attribute1,
2183                        attribute2,
2184                        attribute3,
2185                        attribute4,
2186                        attribute5,
2187                        attribute6,
2188                        attribute7,
2189                        attribute8,
2190                        attribute9,
2191                        attribute10,
2192                        attribute11,
2193                        attribute12,
2194                        attribute13,
2195                        attribute14,
2196                        attribute15,
2197                        receipt_method_name,
2198                        waybill_number,
2199                        document_sequence_name,
2200                        document_sequence_value,
2201                        start_date_commitment,
2202                        end_date_commitment,
2203                        invoicing_rule_name,
2204                        customer_bank_account_name,
2205                        deposit_date,
2206                        factor_discount_amount,
2207                        interface_header_context,
2208                        interface_header_attribute1,
2209                        interface_header_attribute2,
2210                        interface_header_attribute3,
2211                        interface_header_attribute4,
2212                        interface_header_attribute5,
2213                        interface_header_attribute6,
2214                        interface_header_attribute7,
2215                        interface_header_attribute8,
2216                        interface_header_attribute9,
2217                        interface_header_attribute10,
2218                        interface_header_attribute11,
2219                        interface_header_attribute12,
2220                        interface_header_attribute13,
2221                        interface_header_attribute14,
2222                        interface_header_attribute15,
2223                        bank_deposit_number,
2224                        reference_type,
2225                        reference_id,
2226                        customer_receipt_reference,
2227                        bank_account_name
2228                      )
2229                      VALUES
2230                      ( lpad(p_archive_id,14,'0'), /* modified for bug 3266428 */
2231                        select_header.type,
2232                        select_header.name,
2233                        select_header.trx_id,
2234                        select_header.related_trx_type,
2235                        select_header.related_trx_id,
2236                        select_header.prev_trx_id ,
2237                        select_header.trx_number,
2238                        select_header.trx_date,
2239                        select_header.batch_name,
2240                        select_header.batch_source_name,
2241                        select_header.sob_name,
2242                        select_header.amount,
2243                        -- select_header.acctd_amount, --bug1199027
2244                        select_header.exch_gain_loss,
2245                        select_header.earned_disc_taken,
2246                        select_header.unearned_disc_taken,
2247                        -- select_header.acctd_earned_disc_taken, --bug1199027
2248                        -- select_header.acctd_unearned_disc_taken, --bug1199027
2249                        select_header.adj_trx_type,
2250                        select_header.adj_type,
2251                        select_header.post_to_gl,
2252                        select_header.open_receivable,
2253                        select_header.cash_rcpt_status,
2254                        select_header.cash_rcpt_hist_status,
2255                        select_header.reason_code,
2256                        select_header.bill_to_cust_name,
2257                        select_header.bill_to_cust_no,
2258                        select_header.bill_to_cust_loc,
2259                        select_header.bill_to_cust_addr1,
2260                        select_header.bill_to_cust_addr2,
2261                        select_header.bill_to_cust_addr3,
2262                        select_header.bill_to_cust_addr4,
2263                        select_header.bill_to_cust_city,
2264                        select_header.bill_to_cust_state,
2265                        select_header.bill_to_cust_country,
2266                        select_header.bill_to_cust_zip,
2267                        select_header.ship_to_cust_name,
2268                        select_header.ship_to_cust_no,
2269                        select_header.ship_to_cust_loc,
2270                        select_header.ship_to_cust_addr1,
2271                        select_header.ship_to_cust_addr2,
2272                        select_header.ship_to_cust_addr3,
2273                        select_header.ship_to_cust_addr4,
2274                        select_header.ship_to_cust_city,
2275                        select_header.ship_to_cust_state,
2276                        select_header.ship_to_cust_country,
2277                        select_header.ship_to_cust_zip,
2278                        select_header.remit_to_cust_addr1,
2279                        select_header.remit_to_cust_addr2,
2280                        select_header.remit_to_cust_addr3,
2281                        select_header.remit_to_cust_addr4,
2282                        select_header.remit_to_cust_city,
2283                        select_header.remit_to_cust_state,
2284                        select_header.remit_to_cust_country,
2285                        select_header.remit_to_cust_zip,
2286                        select_header.salesrep_name,
2287                        select_header.term_name,
2288                        select_header.term_due_date,
2289                        select_header.last_printed,
2290                        select_header.printing_option,
2291                        select_header.purchase_order,
2292                        select_header.comments,
2293                        select_header.exch_rate_type,
2294                        select_header.exch_date,
2295                        select_header.exch_rate,
2296                        select_header.curr_code,
2297                        select_header.gl_date,
2298                        select_header.reversal_date,
2299                        select_header.reversal_category,
2300                        select_header.reversal_reason_code,
2301                        select_header.reversal_comments,
2302                        select_header.attr_category,
2303                        select_header.attr1,
2304                        select_header.attr2,
2305                        select_header.attr3,
2306                        select_header.attr4,
2307                        select_header.attr5,
2308                        select_header.attr6,
2309                        select_header.attr7,
2310                        select_header.attr8,
2311                        select_header.attr9,
2312                        select_header.attr10,
2313                        select_header.attr11,
2314                        select_header.attr12,
2315                        select_header.attr13,
2316                        select_header.attr14,
2317                        select_header.attr15,
2318                        select_header.rcpt_method,
2319                        select_header.waybill_no,
2320                        select_header.doc_name,
2321                        select_header.doc_seq_value,
2322                        select_header.st_date_commitment,
2323                        select_header.en_date_commitment,
2324                        select_header.invoicing_rule,
2325                        select_header.bank_acct_name,
2326                        select_header.deposit_date,
2327                        select_header.factor_disc_amount,
2328                        select_header.int_hdr_context,
2329                        select_header.int_hdr_attr1,
2330                        select_header.int_hdr_attr2,
2331                        select_header.int_hdr_attr3,
2332                        select_header.int_hdr_attr4,
2333                        select_header.int_hdr_attr5,
2334                        select_header.int_hdr_attr6,
2335                        select_header.int_hdr_attr7,
2336                        select_header.int_hdr_attr8,
2337                        select_header.int_hdr_attr9,
2338                        select_header.int_hdr_attr10,
2339                        select_header.int_hdr_attr11,
2340                        select_header.int_hdr_attr12,
2341                        select_header.int_hdr_attr13,
2342                        select_header.int_hdr_attr14,
2343                        select_header.int_hdr_attr15,
2344                        select_header.bank_deposit_no,
2345                        select_header.reference_type,
2346                        select_header.reference_id,
2347                        select_header.cust_rcpt_reference,
2348                        select_header.bank_acct_name2
2349                      ) ;
2350 
2351                      -- bug1199027
2352                      l_status := ins_control_detail_table ( NVL(select_header.acctd_amount,0),
2353                                                            select_header.type,
2354                                                            NVL(select_header.open_receivable,'Y'),
2355                                                            l_period_name,
2356                                                            p_archive_id  ) ;
2357 
2358                      IF select_header.type = 'CASH'
2359                      THEN
2360                         l_total_discount := NVL(select_header.acctd_earned_disc_taken,0) +
2361                                                  NVL(select_header.acctd_unearned_disc_taken,0);
2362                         IF l_total_discount IS NOT NULL
2363                         THEN
2364                             -- bug1199027
2365                             l_status := ins_control_detail_table ( l_total_discount,
2366                                                                   'DISC',
2367                                                                   NVL(select_header.open_receivable,'Y'),
2368                                                                   l_period_name,
2369                                                                   p_archive_id  ) ;
2370                         END IF ;
2371                         --
2372                         IF select_header.exch_gain_loss IS NOT NULL
2373                         THEN
2374                             -- bug1199027
2375                             l_status := ins_control_detail_table ( select_header.exch_gain_loss,
2376                                                                   'EXCH',
2377                                                                   NVL(select_header.open_receivable,'Y'),
2378                                                                   l_period_name,
2379                                                                   p_archive_id  ) ;
2380                         END IF ;
2381                      END IF ;
2382 
2383                  EXCEPTION
2384                      WHEN OTHERS THEN
2385                          print( 1, 'Failed while inserting into AR_ARCHIVE_HEADER') ;
2386                          print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
2387                          RAISE ;
2388                  END ;
2389 
2390             END LOOP ;
2391 
2392             RETURN ( TRUE );
2393 
2394         EXCEPTION
2395             WHEN OTHERS THEN
2396                 print( 1, '  ...Failed while inserting into AR_ARCHIVE_HEADER');
2397                 print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
2398                 RAISE ;
2399         END ;
2400     END ;
2401 
2402     --
2403     -- Insert into archive_detail
2404     --
2405     FUNCTION archive_detail( p_customer_trx_id IN NUMBER     ,
2406                              p_archive_level   IN VARCHAR2   ,
2407                              p_archive_id      IN NUMBER     ) RETURN BOOLEAN  IS
2408         CURSOR detail_cursor ( cp_customer_trx_id NUMBER ,
2409                                cp_archive_level   VARCHAR2 ,
2410                                cp_org_profile     VARCHAR2 ) IS
2411         SELECT
2412         ctt.type       trx_class,      /* transaction_class */
2413         ctt.name       trx_type,      /* transaction_type */
2414         ct.customer_trx_id trx_id,     /* transaction_id */
2415         ctl.customer_trx_line_id line_id,  /* transaction_line_id */
2416         decode(ctt.type,     /* related_transaction_class */
2417             'CM', ctt_prev.type) related_trx_class,
2418         decode(ctt.type,'CM', ctt_prev.name)
2419             related_trx_type,  /* related_transaction_type */
2420         decode(ctt.type,'CM', ct.previous_customer_trx_id)
2421             related_trx_id,  /* related_transaction_id */
2422         decode(ctt.type, 'CM', ctl.previous_customer_trx_line_id)
2423             related_trx_line_id,  /* related_transaction_line_id */
2424         ctl.line_number line_number,
2425         'LINE' dist_type,       /* distribution_type */
2426         '' app_type,        /* application_type */
2427         lu_line.meaning line_code_meaning,    /* line_code_meaning */
2428         ctl.description description,
2429         /* item_name */
2430         rtrim( mtl.segment1 || '.' ||
2431             mtl.segment2 || '.' ||
2432             mtl.segment3 || '.' ||
2433             mtl.segment4 || '.' ||
2434             mtl.segment5 || '.' ||
2435             mtl.segment6 || '.' ||
2436             mtl.segment7 || '.' ||
2437             mtl.segment8 || '.' ||
2438             mtl.segment9 || '.' ||
2439             mtl.segment10|| '.' ||
2440             mtl.segment11|| '.' ||
2441             mtl.segment12|| '.' ||
2442             mtl.segment13|| '.' ||
2443             mtl.segment14|| '.' ||
2444             mtl.segment15|| '.' ||
2445             mtl.segment16|| '.' ||
2446             mtl.segment17|| '.' ||
2447             mtl.segment18|| '.' ||
2448             mtl.segment19|| '.' ||
2449             mtl.segment20, '.' ) item_name,
2450         nvl(ctl.quantity_invoiced, ctl.quantity_credited) qty, /* qty */
2451         ctl.unit_selling_price selling_price,
2452         ctl.line_type line_type,
2453         ctl.attribute_category attr_category,
2454         ctl.attribute1 attr1,
2455         ctl.attribute2 attr2,
2456         ctl.attribute3 attr3,
2457         ctl.attribute4 attr4,
2458         ctl.attribute5 attr5,
2459         ctl.attribute6 attr6,
2460         ctl.attribute7 attr7,
2461         ctl.attribute8 attr8,
2462         ctl.attribute9 attr9,
2463         ctl.attribute10 attr10,
2464         ctl.attribute11 attr11,
2465         ctl.attribute12 attr12,
2466         ctl.attribute13 attr13,
2467         ctl.attribute14 attr14,
2468         ctl.attribute15 attr15,
2469         ctl.extended_amount amount,            /* amount */
2470         to_number('') acctd_amount,      /* acctd_amount */
2471         ctl.uom_code uom_code,
2472         '' ussgl_trx_code,        /* ussgl_transaction_code */
2473         ctl.tax_rate tax_rate,
2474         vt.tax_code tax_code,
2475         ctl.tax_precedence tax_precedence,
2476         to_number('') ccid1,    /* account_ccid1 */
2477         to_number('') ccid2,   /* account_ccid2 */
2478         to_number('') ccid3,   /* account_ccid3 */
2479         to_number('') ccid4,   /* account_ccid4 */
2480         to_date(NULL) gl_date,  /* gl_date */
2481         to_date(NULL) gl_posted_date, /* gl_posted_date */
2482         rule1.name rule_name,      /* accounting_rule_name */
2483         ctl.accounting_rule_duration acctg_rule_duration,
2484         ctl.rule_start_date rule_start_date,
2485         ctl.last_period_to_credit last_period_to_credit,
2486         '' line_comment,    /* line_comment */
2487         to_number('') line_adjusted,  /* line_adjusted */
2488         to_number('') freight_adjusted, /* freight_adjusted */
2489         to_number('') tax_adjusted,  /* tax_adjusted */
2490         to_number('') charges_adjusted, /* receivables_charges_adjusted */
2491         to_number('') line_applied,  /* line_applied */
2492         to_number('') freight_applied,  /* freight_applied */
2493         to_number('') tax_applied,  /* tax_applied */
2494         to_number('') charges_applied,  /* receivables_charges_applied */
2495         to_number('') earned_disc_taken,/* earned_discount_taken */
2496         to_number('') unearned_disc_taken,      /* unearned_discount_taken */
2497         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
2498         to_number('') acctd_amount_applied_to,  /* acctd_amount_applied_to */
2499         to_number('') acctd_earned_disc_taken,  /* acctd_earned_disc_taken */
2500         to_number('') acctd_unearned_disc_taken,  /* acctd_unearned_disc_taken */
2501         to_number('') factor_discount_amount,  /* factor_discount_amount */
2502         to_number('') acctd_factor_discount_amount,  /* acctd_factor_discount_amount */
2503         ctl.interface_line_context int_line_context,
2504         ctl.interface_line_attribute1 int_line_attr1,
2505         ctl.interface_line_attribute2 int_line_attr2,
2506         ctl.interface_line_attribute3 int_line_attr3,
2507         ctl.interface_line_attribute4 int_line_attr4,
2508         ctl.interface_line_attribute5 int_line_attr5,
2509         ctl.interface_line_attribute6 int_line_attr6,
2510         ctl.interface_line_attribute7 int_line_attr7,
2511         ctl.interface_line_attribute8 int_line_attr8,
2512         ctl.interface_line_attribute9 int_line_attr9,
2513         ctl.interface_line_attribute10 int_line_attr10,
2514         ctl.interface_line_attribute11 int_line_attr11,
2515         ctl.interface_line_attribute12 int_line_attr12,
2516         ctl.interface_line_attribute13 int_line_attr13,
2517         ctl.interface_line_attribute14 int_line_attr14,
2518         ctl.interface_line_attribute15 int_line_attr15,
2519         '' exch_rate_type,      /* exchange_rate_type */
2520         to_date(NULL) exch_date,      /* exchange_rate_date */
2521         to_number('') exch_rate,     /* exchange_rate */
2522         to_date(NULL) due_date,      /* due_date */
2523         to_date(NULL) apply_date,      /* apply_date */
2524         ctl.movement_id movement_id,
2525         ctl.tax_vendor_return_code vendor_return_code,
2526         /* tax_authorities_tax_rate */
2527         rtrim( to_char(st.location1_rate) || ' ' ||
2528         to_char(st.location2_rate) || ' ' ||
2529         to_char(st.location3_rate) || ' ' ||
2530         to_char(st.location4_rate) || ' ' ||
2531         to_char(st.location5_rate) || ' ' ||
2532         to_char(st.location6_rate) || ' ' ||
2533         to_char(st.location7_rate) || ' ' ||
2534         to_char(st.location8_rate) || ' ' ||
2535         to_char(st.location9_rate) || ' ' ||
2536         to_char(st.location10_rate), ' ' ) tax_auth_tax_rate,
2537         ctl.tax_exempt_flag tax_exempt_flag,
2538         ctl.tax_exemption_id tax_exemption_id,
2539         te.exemption_type exemption_type,
2540         nvl(lu_te.meaning, lu_line2.meaning) tax_exemption_reason,/* tax_exemption_reason */
2541         nvl(te.customer_exemption_number, ctl.tax_exempt_number)
2542              tax_exemption_number, /* tax_exemption_number */
2543         /* item_exception_rate */
2544         rtrim( to_char(ier.location1_rate) || ' ' ||
2545         to_char(ier.location2_rate) || ' ' ||
2546         to_char(ier.location3_rate) || ' ' ||
2547         to_char(ier.location4_rate) || ' ' ||
2548         to_char(ier.location5_rate) || ' ' ||
2549         to_char(ier.location6_rate) || ' ' ||
2550         to_char(ier.location7_rate) || ' ' ||
2551         to_char(ier.location8_rate) || ' ' ||
2552         to_char(ier.location9_rate) || ' ' ||
2553         to_char(ier.location10_rate), ' ' ) item_exception_rate ,
2554         lu_ier.meaning meaning,      /* exception_reason */
2555         dl.original_collectibility_flag,      /* original_collectibility_flag */
2556         dl.line_collectible_flag,             /* line_collectible_flag */
2557         dl.manual_override_flag,              /* manual_override_flag */
2558         ''   contingency_code,    /* contingency_code */
2559         to_date(null) expiration_date,  /* expiration_date */
2560         to_number('') expiration_days,  /* expiration_days */
2561         ctl.override_auto_accounting_flag  /* override_auto_accounting_flag */
2562         FROM
2563         ar_lookups lu_te,
2564         ra_tax_exemptions te,
2565         ar_lookups lu_ier,
2566         ra_item_exception_rates ier,
2567         ar_sales_tax      st,
2568         ar_vat_tax        vt,
2569         ar_lookups        lu_line,
2570         ar_lookups        lu_line2,
2571         ra_rules          rule1,
2572         ra_cust_trx_types ctt_prev,
2573         ra_cust_trx_types ctt,
2574         mtl_system_items  mtl,
2575         ra_customer_trx_lines    ctl,
2576         ra_customer_trx   ct_prev,
2577         ra_customer_trx   ct,
2578   ar_deferred_lines dl
2579         WHERE te.tax_exemption_id (+) = ctl.tax_exemption_id
2580         AND   te.reason_code = lu_te.lookup_code (+)
2581         AND   lu_te.lookup_type (+) = 'TAX_REASON'
2582         AND   ier.item_exception_rate_id (+) = ctl.item_exception_rate_id
2583         AND   ier.reason_code = lu_ier.lookup_code (+)
2584         AND   lu_ier.lookup_type (+) = 'TAX_EXCEPTION_REASON'
2585         AND   st.sales_tax_id (+)    = ctl.sales_tax_id
2586         AND   vt.vat_tax_id (+)      = ctl.vat_tax_id
2587         AND   lu_line.lookup_code (+)    = ctl.reason_code
2588         AND   lu_line.lookup_type (+)    = 'INVOICING_REASON'
2589         AND   lu_line2.lookup_code (+)    = ctl.tax_exempt_reason_code
2590         AND   lu_line2.lookup_type (+)    = 'TAX_REASON'
2591         AND   rule1.rule_id (+)        = ctl.accounting_rule_id
2592         AND   ctt.cust_trx_type_id    = ct.cust_trx_type_id
2593         AND   mtl.inventory_item_id (+) = ctl.inventory_item_id
2594         AND   mtl.organization_id (+) = to_number(cp_org_profile)
2595         AND   ctl.customer_trx_id = ct.customer_trx_id
2596         AND   ct.previous_customer_trx_id = ct_prev.customer_trx_id(+)
2597         AND   ct_prev.cust_trx_type_id = ctt_prev.cust_trx_type_id(+)
2598         AND   ct.customer_trx_id     = cp_customer_trx_id
2599         AND   cp_archive_level <> 'H'
2600         AND   ctl.customer_trx_line_id = dl.customer_trx_line_id(+)
2601         UNION ALL /* Bug 5105156 - fix 5044763 */
2602         ---------------------------------------------------------------------
2603         -- TRX distributions
2604         -- 'A' level only
2605         ---------------------------------------------------------------------
2606         SELECT
2607         ctt.type trx_class,      /* transaction_class */
2608         ctt.name trx_type,      /* transaction_type */
2609         ct.customer_trx_id trx_id,     /* transaction_id */
2610         ctlgd.customer_trx_line_id line_id,  /* transaction_line_id */
2611         '' related_trx_class,      /* related_transaction_class */
2612         '' related_trx_type,      /* related_transaction_type */
2613         to_number('') related_trx_id,     /* related_transaction_id */
2614         to_number('') related_trx_line_id,  /* related_transaction_line_id */
2615         to_number('') line_number,    /* line_number */
2616         ctlgd.account_class dist_type,     /* distribution_type */
2617         '' app_type,        /* application_type */
2618         '' line_code_meaning,       /* line_code_meaning */
2619         '' description,                         /* description */
2620         '' item_name,                           /* item_name */
2621         to_number('') qty,       /* qty */
2622         to_number('') selling_price,    /* unit_selling_price */
2623         '' line_type,        /* line_type */
2624         ctlgd.attribute_category attr_category,
2625         ctlgd.attribute1 attr1,
2626         ctlgd.attribute2 attr2,
2627         ctlgd.attribute3 attr3,
2628         ctlgd.attribute4 attr4,
2629         ctlgd.attribute5 attr5,
2630         ctlgd.attribute6 attr6,
2631         ctlgd.attribute7 attr7,
2632         ctlgd.attribute8 attr8,
2633         ctlgd.attribute9 attr9,
2634         ctlgd.attribute10 attr10,
2635         ctlgd.attribute11 attr11,
2636         ctlgd.attribute12 attr12,
2637         ctlgd.attribute13 attr13,
2638         ctlgd.attribute14 attr14,
2639         ctlgd.attribute15 attr15,
2640         ctlgd.amount amount,
2641         ctlgd.acctd_amount acctd_amount,
2642         '' uom_code,     /* uom code */
2643         ctlgd.ussgl_transaction_code ussgl_trx_code,
2644         to_number('') tax_rate,      /* tax_rate */
2645         '' tax_code,         /* tax_code */
2646         to_number('') tax_precedence,    /* tax_precedence */
2647         ctlgd.code_combination_id ccid1,        /* account_ccid1 */
2648         to_number('') ccid2,     /* account_ccid2 */
2649         to_number('') ccid3,     /* account_ccid3 */
2650         to_number('') ccid4,     /* account_ccid4 */
2651         nvl(ctlgd.gl_date, ct.trx_date) gl_date,/* gl_date */
2652         ctlgd.gl_posted_date gl_posted_date,  /* gl_posted_date */
2653         '' acctg_rule_name,      /* accounting_rule_name */
2654         to_number('') acctg_rule_duration,  /* accounting_rule_duration */
2655         to_date(NULL) rule_start_date,    /* rule_start_date */
2656         to_number('') last_period_to_credit,  /* last_period_to_credit */
2657         '' line_amount,        /* line_comment */
2658         to_number('') line_adjusted,    /* line_adjusted */
2659         to_number('') freight_adjusted,          /* freight_adjusted */
2660         to_number('') tax_adjusted,    /* tax_adjusted */
2661         to_number('') charges_adjusted,          /* receivables_charges_adjusted */
2662         to_number('') line_applied,    /* line_applied */
2663         to_number('') freight_applied,    /* freight_applied */
2664         to_number('') tax_applied,    /* tax_applied */
2665         to_number('') charges_applied,    /* receivables_charges_applied */
2666         to_number('') earned_disc_taken,  /* earned_discount_taken */
2667         to_number('') unearned_disc_taken,  /* unearned_discount_taken */
2668         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
2669         to_number('') acctd_amount_applied_to,  /* acctd_amount_applied_to */
2670         to_number('') acctd_earned_disc_taken,  /* acctd_earned_disc_taken */
2671         to_number('') acctd_unearned_disc_taken,/* acctd_unearned_disc_taken */
2672         to_number('') factor_discount_amount,  /* factor_discount_amount */
2673         to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
2674         '' int_line_context, /* interface_line_context */
2675         '' int_line_attr1,   /* interface_line_attribute1 */
2676         '' int_line_attr2,   /* interface_line_attribute2 */
2677         '' int_line_attr3,   /* interface_line_attribute3 */
2678         '' int_line_attr4,   /* interface_line_attribute4 */
2679         '' int_line_attr5,   /* interface_line_attribute5 */
2680         '' int_line_attr6,   /* interface_line_attribute6 */
2681         '' int_line_attr7,   /* interface_line_attribute7 */
2682         '' int_line_attr8,   /* interface_line_attribute8 */
2683         '' int_line_attr9,    /* interface_line_attribute9 */
2684         '' int_line_attr10,    /* interface_line_attribute10 */
2685         '' int_line_attr11,    /* interface_line_attribute11 */
2686         '' int_line_attr12,    /* interface_line_attribute12 */
2687         '' int_line_attr13,    /* interface_line_attribute13 */
2688         '' int_line_attr14,    /* interface_line_attribute14 */
2689         '' int_line_attr15,    /* interface_line_attribute15 */
2690         '' exchange_rate_type,    /* exchange_rate_type */
2691         to_date(NULL) exch_date,    /* exchange_rate_date */
2692         to_number('') exch_rate,   /* exchange_rate */
2693         to_date(NULL) due_date,    /* due_date */
2694         to_date(NULL) apply_date,          /* apply_date */
2695         to_number('') movement_id,  /* movement_id */
2696         '' tax_vendor_return_code,  /* tax_vendor_return_code */
2697         '' tax_auth_tax_rate,            /* tax_authorities_tax_rate */
2698         '' tax_exempt_flag,    /* tax_exemption_flag */
2699         to_number('') tax_exemption_id, /* tax_exemption_id */
2700         '' exemption_type,    /* exemption_type */
2701         '' tax_exemption_reason,  /* exemption_reason */
2702         '' tax_exemption_number,  /* customer_exemption_number */
2703         '' item_exception_rate,    /* item_exception_rate */
2704         '' meaning,      /* exception_reason */
2705         '',                             /* original_collectibility_flag */
2706         '',                             /* line_collectible_flag */
2707         '',                             /* manual_override_flag */
2708         '',                             /* contingency_code */
2709         to_date(null),                  /* expiration_date */
2710         to_number(null),                /* expiration_days */
2711   ''      /* override_auto_accounting_flag */
2712         FROM
2713         ra_cust_trx_types ctt,
2714         ra_cust_trx_line_gl_dist ctlgd,
2715         ra_customer_trx   ct
2716         WHERE  ctt.cust_trx_type_id  = ct.cust_trx_type_id
2717         AND    ctlgd.customer_trx_id = ct.customer_trx_id
2718         AND    ctlgd.account_set_flag <> 'Y'  /* no acount sets */
2719         AND    decode(ctlgd.account_class, 'REC',
2720                    ctlgd.latest_rec_flag, 'Y') = 'Y'
2721         AND    ct.customer_trx_id     = cp_customer_trx_id
2722         AND    cp_archive_level = 'A'
2723         UNION ALL /* Bug 5105156 - fix 5044763 */
2724         ---------------------------------------------------------------------
2725                -- TRX adjustments (ADJ)
2726                -- 'L', 'A' levels
2727         ---------------------------------------------------------------------
2728         SELECT
2729         'ADJ' trx_class,            /* transaction_class */
2730         ''    trx_type,              /* transaction_type */
2731         adj.adjustment_id trx_id,   /* transaction_id */
2732         to_number('') line_id,    /* transaction_line_id */
2733         ctt.type related_trx_class,    /* related_transaction_class */
2734         ctt.name related_trx_type,    /* related_transaction_type */
2735         ct.customer_trx_id related_trx_id,   /* related_transaction_id */
2736         to_number('') related_trx_line_id,    /* related_transaction_line_id */
2737         to_number('') line_number,   /* line_number */
2738         'ADJ' dist_type,     /* distribution_type */
2739         '' app_type,      /* application_type */
2740         '' line_code_meaning,       /* line_code_meaning */
2741         '' description,      /* description */
2742         '' item_name,      /* item_name */
2743         to_number('') qty,    /* quantity */
2744         to_number('') selling_price,  /* unit_selling_price */
2745         '' line_type,      /* line_type */
2746         adj.attribute_category attr_category,
2747         adj.attribute1 attr1,
2748         adj.attribute2 attr2,
2749         adj.attribute3 attr3,
2750         adj.attribute4 attr4,
2751         adj.attribute5 attr5,
2752         adj.attribute6 attr6,
2753         adj.attribute7 attr7,
2754         adj.attribute8 attr8,
2755         adj.attribute9 attr9,
2756         adj.attribute10 attr10,
2757         adj.attribute11 attr11,
2758         adj.attribute12 attr12,
2759         adj.attribute13 attr13,
2760         adj.attribute14 attr14,
2761         adj.attribute15 attr15,
2762         adj.amount amount,
2763         adj.acctd_amount acctd_amount,
2764         '' uom_code,    /* uom_code */
2765         '' ussgl_trx_code,  /* ussgl_transaction_code */
2766         to_number('') tax_rate,/* tax_rate */
2767         '' tax_code,    /* tax_code */
2768         to_number('') tax_precedence,  /* tax_precedence */
2769         adj.code_combination_id ccid1,   /* account_ccid1 */
2770         to_number('') ccid2,  /* account_ccid2 */
2771         to_number('') ccid3,  /* account_ccid3 */
2772         to_number('') ccid4,  /* account_ccid4 */
2773         adj.gl_date gl_date,
2774         adj.gl_posted_date gl_posted_date,
2775         '' acctg_rule_duration,  /* acct_rule_name */
2776         to_number('') rule_name, /* rule_duration */
2777         to_date(NULL) rule_start_date,  /* rule_start_date */
2778         to_number('') last_period_to_credit,  /* last_period_to_credit */
2779         '' line_comment,      /* line_comment */
2780         adj.line_adjusted line_adjusted,  /* line_adjusted */
2781         adj.freight_adjusted freight_adjusted,  /* freight_adjusted */
2782         adj.tax_adjusted tax_adjusted,  /* tax_adjusted */
2783         adj.receivables_charges_adjusted charges_adjusted, /* receivables_charges_adjusted */
2784         to_number('') line_applied,    /* line_applied */
2785         to_number('') freight_applied,    /* freight_applied */
2786         to_number('') tax_applied,    /* tax_applied */
2787         to_number('') charges_applied,    /* receivables_charges_applied */
2788         to_number('') earned_disc_taken,  /* earned_discount_taken */
2789         to_number('') unearned_disc_taken,  /* unearned_discount_taken */
2790         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
2791         to_number('') acctd_amount_applied_to,   /* acctd_amount_applied_to */
2792         to_number('') acctd_earned_disc_taken,    /* acctd_earned_disc_taken */
2793         to_number('') acctd_unearned_disc_taken,  /* acctd_unearned_disc_taken */
2794         to_number('') factor_discount_amount,    /* factor_discount_amount */
2795         to_number('') acctd_factor_discount_amount,  /* acctd_factor_discount_amount */
2796         '' int_line_context,    /* interface_line_context */
2797         '' int_line_attr1,    /* interface_line_attribute1 */
2798         '' int_line_attr2,    /* interface_line_attribute2 */
2799         '' int_line_attr3,     /* interface_line_attribute3 */
2800         '' int_line_attr4,    /* interface_line_attribute4 */
2801         '' int_line_attr5,    /* interface_line_attribute5 */
2802         '' int_line_attr6,     /* interface_line_attribute6 */
2803         '' int_line_attr7,     /* interface_line_attribute7 */
2804         '' int_line_attr8,     /* interface_line_attribute8 */
2805         '' int_line_attr9,     /* interface_line_attribute9 */
2806         '' int_line_attr10,     /* interface_line_attribute10 */
2807         '' int_line_attr11,     /* interface_line_attribute11 */
2808         '' int_line_attr12,     /* interface_line_attribute12 */
2809         '' int_line_attr13,     /* interface_line_attribute13 */
2810         '' int_line_attr14,     /* interface_line_attribute14 */
2811         '' int_line_attr15,    /* interface_line_attribute15 */
2812         '' exch_rate_type,   /* exchange_rate_type */
2813         to_date(NULL) exch_date,  /* exchange_rate_date */
2814         to_number('') exch_rate,/* exchange_rate */
2815         to_date(NULL) due_date,    /* due_date */
2816         to_date(NULL) apply_date,  /* apply_date */
2817         to_number('') movement_id,  /* movement_id */
2818         '' vendor_return_code,    /* tax_vendor_return_code */
2819         '' tax_auth_tax_rate,    /* tax_authority_tax_rates */
2820         '' tax_exempt_flag,    /* tax_exemption_flag */
2821         to_number('') tax_exemption_id,/* tax_exemption_id */
2822         '' exemption_type,    /* exemption_type */
2823         '' tax_exemption_reason,  /* exemption_reason */
2824         '' tax_exemption_number,  /* customer_exemption_number */
2825         '' item_exception_rate,  /* item_exception_rate */
2826         '' meaning,      /* item_exception_reason */
2827         '',                             /* original_collectibility_flag */
2828         '',                             /* line_collectible_flag */
2829         '',                             /* manual_override_flag */
2830         '',                             /* contingency_code */
2831         to_date(null),                  /* expiration_date */
2832         to_number(null),                /* expiration_days */
2833   ''      /* override_auto_accounting_flag */
2834         FROM   ra_cust_trx_types ctt,
2835                ra_customer_trx   ct,
2836                ar_adjustments    adj
2837         WHERE  adj.customer_trx_id     = cp_customer_trx_id
2838         and    adj.customer_trx_id     = ct.customer_trx_id
2839         and    ctt.cust_trx_type_id    = ct.cust_trx_type_id
2840         and    cp_archive_level <> 'H'
2841   UNION ALL /* Bug 5105156 - fix 5044763 */
2842   ---------------------------------------------------------------------
2843         -- TRX contingencies (CONTINGENCY)
2844         -- 'L', 'A' levels
2845   ---------------------------------------------------------------------
2846   SELECT
2847   'CONTINGENCY',      /* transaction_class */
2848   '',         /* transaction_type */
2849   ctl.customer_trx_id,    /* transaction_id */
2850   ctl.customer_trx_line_id,  /* transaction_line_id */
2851   '',        /* related_transaction_class */
2852   '',        /* related_transaction_type */
2853   to_number(''),      /* related_transaction_id */
2854   to_number(''),      /* related_transaction_line_id */
2855   to_number(''),       /* line_number */
2856   '',         /* distribution_type */
2857         '',        /* application_type */
2858   '',         /* line_code_meaning */
2859   '',        /* description */
2860   '',        /* item_name */
2861   to_number(''),      /* quantity */
2862   to_number(''),      /* unit_selling_price */
2863   '',        /* line_type */
2864   '',
2865   '',
2866   '',
2867   '',
2868   '',
2869   '',
2870   '',
2871   '',
2872   '',
2873   '',
2874   '',
2875   '',
2876   '',
2877   '',
2878   '',
2879   '',
2880   to_number(''),
2881   to_number(''),
2882   '',        /* uom_code */
2883   '',        /* ussgl_transaction_code */
2884   to_number(''),      /* tax_rate */
2885   '',        /* tax_code */
2886   to_number(''),      /* tax_precedence */
2887   to_number(''),       /* account_ccid1 */
2888   to_number(''),      /* account_ccid2 */
2889   to_number(''),      /* account_ccid3 */
2890   to_number(''),      /* account_ccid4 */
2891   to_date(null),
2892   to_date(null),
2893         '',        /* acct_rule_name */
2894         to_number(''),       /* rule_duration */
2895         to_date(null),      /* rule_start_date */
2896         to_number(''),      /* last_period_to_credit */
2897         '',          /* line_comment */
2898   to_number(''),      /* line_adjusted */
2899   to_number(''),      /* freight_adjusted */
2900   to_number(''),      /* tax_adjusted */
2901   to_number(''),      /* receivables_charges_adjusted */
2902   to_number(''),      /* line_applied */
2903   to_number(''),      /* freight_applied */
2904   to_number(''),      /* tax_applied */
2905   to_number(''),      /* receivables_charges_applied */
2906   to_number(''),      /* earned_discount_taken */
2907   to_number(''),      /* unearned_discount_taken */
2908   to_number(''),      /* acctd_amount_applied_from */
2909   to_number(''),      /* acctd_amount_applied_to */
2910   to_number(''),      /* acctd_earned_disc_taken */
2911   to_number(''),      /* acctd_unearned_disc_taken */
2912   to_number(''),      /* factor_discount_amount */
2913   to_number(''),      /* acctd_factor_discount_amount */
2914   '',          /* interface_line_context */
2915   '',          /* interface_line_attribute1 */
2916   '',          /* interface_line_attribute2 */
2917   '',           /* interface_line_attribute3 */
2918   '',          /* interface_line_attribute4 */
2919   '',          /* interface_line_attribute5 */
2920   '',           /* interface_line_attribute6 */
2921   '',           /* interface_line_attribute7 */
2922   '',           /* interface_line_attribute8 */
2923   '',           /* interface_line_attribute9 */
2924   '',           /* interface_line_attribute10 */
2925   '',           /* interface_line_attribute11 */
2926   '',           /* interface_line_attribute12 */
2927   '',           /* interface_line_attribute13 */
2928   '',           /* interface_line_attribute14 */
2929   '',            /* interface_line_attribute15 */
2930   '',         /* exchange_rate_type */
2931   to_date(null),      /* exchange_rate_date */
2932         to_number(''),      /* exchange_rate */
2933   to_date(null),      /* due_date */
2934   to_date(null),      /* apply_date */
2935         to_number(''),      /* movement_id */
2936         '',        /* tax_vendor_return_code */
2937         '',        /* tax_authority_tax_rates */
2938         '',        /* tax_exemption_flag */
2939         to_number(''),      /* tax_exemption_id */
2940         '',        /* exemption_type */
2941         '',        /* exemption_reason */
2942         '',        /* customer_exemption_number */
2943         '',        /* item_exception_rate */
2944         '',         /* item_exception_reason */
2945   '',        /* original_collectibility_flag */
2946   '',        /* line_collectible_flag */
2947   '',        /* manual_override_flag */
2948   lc.contingency_code,    /* contingency_code */
2949   lc.expiration_date,     /* expiration_date */
2950   lc.expiration_days,    /* expiration_days */
2951   ''      /* override_auto_accounting_flag */
2952   FROM
2953         ra_customer_trx_lines ctl,
2954         ar_line_conts lc
2955   WHERE   cp_customer_trx_id    = ctl.customer_trx_id
2956   and  ctl.customer_trx_line_id   = lc.customer_trx_line_id
2957         and     cp_archive_level <> 'H'
2958         UNION ALL /* Bug 5105156 - fix 5044763 */
2959         ---------------------------------------------------------------------
2960         -- REC information (CRH)
2961         -- all levels
2962         ---------------------------------------------------------------------
2963         SELECT
2964         cr.type trx_class,      /* transaction_class */
2965         '' trx_type,        /* transaction_type */
2966         cr.cash_receipt_id trx_id,    /* transaction_id */
2967         to_number('') line_id,      /* transaction_line_id */
2968         '' related_trx_class,      /* related_transaction_class */
2969         '' related_trx_type,      /* related_transaction_type */
2970         to_number('') related_trx_id,    /* related_transaction_id */
2971         to_number('') related_trx_line_id,  /* related_transaction_line_id */
2972         to_number('') line_number,      /* line_number */
2973         'CRH' dist_type,       /* distribution_type */
2974         '' app_type,        /* application_type */
2975         '' line_code_meaning,      /* line_code_meaning */
2976         '' description,      /* description */
2977         '' item_name,        /* item_name */
2978         to_number('') qty,      /* quantity */
2979         to_number('') selling_price,      /* unit_selling_price */
2980         '' line_type,        /* line_type */
2981         crh.attribute_category attr_category,
2982         crh.attribute1 attr1,
2983         crh.attribute2 attr2,
2984         crh.attribute3 attr3,
2985         crh.attribute4 attr4,
2986         crh.attribute5 attr5,
2987         crh.attribute6 attr6,
2988         crh.attribute7 attr7,
2989         crh.attribute8 attr8,
2990         crh.attribute9 attr9,
2991         crh.attribute10 attr10,
2992         crh.attribute11 attr11,
2993         crh.attribute12 attr12,
2994         crh.attribute13 attr13,
2995         crh.attribute14 attr14,
2996         crh.attribute15 attr15,
2997         crh.amount amount,
2998         crh.acctd_amount acctd_amount,
2999         '' uom_code,          /* uom code */
3000         cr.ussgl_transaction_code ussgl_trx_code,
3001         vt.tax_rate tax_rate,        /* tax_rate */
3002         vt.tax_code tax_code,         /* tax_code */
3003         to_number('') tax_precedence,        /* tax_precedence */
3004         crh.account_code_combination_id ccid1,
3005         crh.bank_charge_account_ccid ccid2,
3006         to_number('') ccid3,       /* account_ccid3 */
3007         to_number('') ccid4,        /* account_ccid4 */
3008         crh.gl_date gl_date,
3009         crh.gl_posted_date gl_posted_date,
3010         '' rule_name,         /* acct_rule_name */
3011         to_number('') acctg_rule_duration,    /* rule_duration */
3012         to_date(NULL) rule_start_date,    /* rule_start_date */
3013         to_number('') last_period_to_credit,   /* last_period_to_credit */
3014         '' line_comment,       /* line_comment */
3015         to_number('') line_adjusted,    /* line_adjusted */
3016         to_number('') freight_adjusted,  /* freight_adjusted */
3017         to_number('') tax_adjusted,    /* tax_adjusted */
3018         to_number('') charges_adjusted,  /* receivables_charges_adjusted */
3019         to_number('') line_applied,    /* line_applied */
3020         to_number('') freight_applied,    /* freight_applied */
3021         to_number('') tax_applied,    /* tax_applied */
3022         to_number('') charges_adjusted,  /* receivables_charges_applied */
3023         to_number('') earned_disc_taken,  /* earned_discount_taken */
3024         to_number('') unearned_disc_taken,  /* unearned_discount_taken */
3025         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
3026         to_number('') acctd_amount_applied_to,  /* acctd_amount_applied_to */
3027         to_number('') acctd_earned_disc_taken,  /* acctd_earned_disc_taken */
3028         to_number('') acctd_unearned_disc_taken,/* acctd_unearned_disc_taken */
3029         crh.factor_discount_amount factor_discount_amount,
3030                 /* factor_discount_amount */
3031         crh.acctd_factor_discount_amount acctd_factor_discount_amount,
3032                 /* acctd_factor_discount_amount */
3033          '' int_line_context,      /* interface_line_context */
3034          '' int_line_attr1,       /* interface_line_attribute1 */
3035          '' int_line_attr2,      /* interface_line_attribute2 */
3036          '' int_line_attr3,      /* interface_line_attribute3 */
3037          '' int_line_attr4,       /* interface_line_attribute4 */
3038          '' int_line_attr5,       /* interface_line_attribute5 */
3039          '' int_line_attr6,       /* interface_line_attribute6 */
3040          '' int_line_attr7,      /* interface_line_attribute7 */
3041          '' int_line_attr8,       /* interface_line_attribute8 */
3042          '' int_line_attr9,      /* interface_line_attribute9 */
3043          '' int_line_attr10,     /* interface_line_attribute10 */
3044          '' int_line_attr11,     /* interface_line_attribute11 */
3045          '' int_line_attr12,     /* interface_line_attribute12 */
3046          '' int_line_attr13,     /* interface_line_attribute13 */
3047          '' int_line_attr14,     /* interface_line_attribute14 */
3048          '' int_line_attr15,       /* interface_line_attribute15 */
3049          crh.exchange_rate_type exch_rate_type,
3050          crh.exchange_date exch_date,
3051          crh.exchange_rate exch_rate,
3052          to_date(NULL) due_date,      /* due_date */
3053          to_date(NULL) apply_date,    /* apply_date */
3054          to_number('') movement_id,    /* movement_id */
3055          '' vendor_return_code,    /* tax_vendor_return_code */
3056          '' tax_auth_tax_rate,      /* tax_authority_tax_rates */
3057          '' tax_exempt_flag,      /* tax_exemption_flag */
3058          to_number('') tax_exemption_id,  /* tax_exemption_id */
3059          '' exemption_type,      /* exemption_type */
3060          '' tax_exemption_reason,    /* exemption_reason */
3061          '' tax_exemption_number,    /* customer_exemption_number */
3062          '' item_exception_rate,    /* item_exception_rate */
3063          '' meaning,                            /* item_exception_reason */
3064          '',                             /* original_collectibility_flag */
3065          '',                             /* line_collectible_flag */
3066          '',                             /* manual_override_flag */
3067          '',                             /* contingency_code */
3068          to_date(null),                  /* expiration_date */
3069          to_number(null),                /* expiration_days */
3070    ''       /* override_auto_accounting_flag */
3071          FROM
3072          ar_vat_tax vt,
3073          ar_cash_receipt_history crh,
3074          ar_cash_receipts  cr ,
3075          ar_receivable_applications ra
3076          WHERE  crh.cash_receipt_id     = cr.cash_receipt_id
3077          and  nvl(crh.current_record_flag, 'N') = 'Y'
3078          and    cr.vat_tax_id = vt.vat_tax_id (+)
3079          and   cr.cash_receipt_id     = ra.cash_receipt_id
3080          and    ra.applied_customer_trx_id = cp_customer_trx_id
3081         -- bug3567865 Don't insert duplicate cash record.
3082         and    not exists (
3083                   select 'already purged'
3084                     from ar_archive_detail aad
3085                    where aad.transaction_id = cr.cash_receipt_id
3086                      and aad.transaction_class = 'CASH' )
3087          UNION ALL /* Bug 5105156 - fix 5044763 */
3088          ---------------------------------------------------------------------
3089          -- REC_APP of
3090          -- all invoices pertaining to the receipt of the invoice
3091          ---------------------------------------------------------------------
3092          SELECT
3093          cr.type trx_class,       /* transaction_class */
3094          '' trx_type,        /* transaction_type */
3095          cr.cash_receipt_id trx_id,    /* transaction_id */
3096          to_number('') line_id,      /* transaction_line_id */
3097          ctt.type related_trx_class,      /* related_transaction_class */
3098          ctt.name related_trx_type,      /* related_transaction_type */
3099          ct.customer_trx_id related_trx_id,    /* related_transaction_id */
3100          to_number('') related_trx_line_id,      /* related_transaction_line_id */
3101          to_number('') line_number,        /* line_number */
3102          'REC_APP' dist_type,       /* distribution_type */
3103          ra.application_type app_type,    /* application_type */
3104          '' line_code_meaning,         /* line_code_meaning */
3105          '' description,        /* description */
3106          '' item_name,        /* item_name */
3107          to_number('') qty,      /* quantity */
3108          to_number('') selling_price,      /* unit_selling_price */
3109          '' line_type,        /* line_type */
3110          ra.attribute_category attr_category,
3111          ra.attribute1 attr1,
3112          ra.attribute2 attr2,
3113          ra.attribute3 attr3,
3114          ra.attribute4 attr4,
3115          ra.attribute5 attr5,
3116          ra.attribute6 attr6,
3117          ra.attribute7 attr7,
3118          ra.attribute8 attr8,
3119          ra.attribute9 attr9,
3120          ra.attribute10 attr10,
3121          ra.attribute11 attr11,
3122          ra.attribute12 attr12,
3123          ra.attribute13 attr13,
3124          ra.attribute14 attr14,
3125          ra.attribute15 attr15,
3126          ra.amount_applied amount, /* amount */
3127          to_number('') acctd_amount,      /* acctd_amount */
3128          '' uom_code,            /* uom code */
3129          cr.ussgl_transaction_code ussgl_trx_code,
3130          to_number('') tax_rate,    /* tax_rate */
3131          '' tax_code,         /* tax_code */
3132          to_number('') tax_precedence,      /* tax_precedence */
3133          ra.code_combination_id ccid1,    /* account_ccid1 */
3134          to_number('') ccid2,        /* account_ccid2 */
3135          ra.earned_discount_ccid ccid3,   /* account_ccid3 */
3136          ra.unearned_discount_ccid ccid4, /* account_ccid4 */
3137          ra.gl_date gl_date,
3138          ra.gl_posted_date gl_posted_date,
3139          '' rule_name,         /* acct_rule_name */
3140          to_number('') acctg_rule_duration,/* rule_duration */
3141          to_date(NULL) rule_start_date,      /* rule_start_date */
3142          to_number('') last_period_to_credit,  /* last_period_to_credit */
3143          ra.comments line_comment,     /* line_comment */
3144          to_number('') line_adjusted,          /* line_adjusted */
3145          to_number('') freight_adjusted,  /* freight_adjusted */
3146          to_number('') tax_adjusted,    /* tax_adjusted */
3147          to_number('') charges_adjusted,  /* receivables_charges_adjusted */
3148          ra.line_applied line_applied,    /* line_applied */
3149          ra.freight_applied freight_applied,  /* freight_applied */
3150          ra.tax_applied tax_applied,    /* tax_applied */
3151          ra.receivables_charges_applied charges_applied,/* receivables_charges_applied */
3152          ra.earned_discount_taken earned_disc_taken,   /* earned_discount_taken */
3153          ra.unearned_discount_taken unearned_disc_taken,/* unearned_discount_taken */
3154          ra.acctd_amount_applied_from acctd_amount_applied_from,
3155                 /* acctd_amount_applied_from */
3156          ra.acctd_amount_applied_to acctd_amount_applied_to,
3157                 /* acctd_amount_applied_to */
3158          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
3159                 /* acctd_earned_disc_taken */
3160          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
3161                 /* acctd_unearned_disc_taken */
3162          to_number('') factor_discount_amount,  /* factor_discount_amount */
3163          to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
3164          '' int_line_context,        /* interface_line_context */
3165          '' int_line_attr1,         /* interface_line_attribute1 */
3166          '' int_line_attr2,        /* interface_line_attribute2 */
3167          '' int_line_attr3,         /* interface_line_attribute3 */
3168          '' int_line_attr4,         /* interface_line_attribute4 */
3169          '' int_line_attr5,         /* interface_line_attribute5 */
3170          '' int_line_attr6,         /* interface_line_attribute6 */
3171          '' int_line_attr7,         /* interface_line_attribute7 */
3172          '' int_line_attr8,         /* interface_line_attribute8 */
3173          '' int_line_attr9,         /* interface_line_attribute9 */
3174          '' int_line_attr10,       /* interface_line_attribute10 */
3175          '' int_line_attr11,       /* interface_line_attribute11 */
3176          '' int_line_attr12,        /* interface_line_attribute12 */
3177          '' int_line_attr13,        /* interface_line_attribute13 */
3178          '' int_line_attr14,        /* interface_line_attribute14 */
3179          '' int_line_attr15,        /* interface_line_attribute15 */
3180          '' exch_rate_type,      /* exchange_rate_type */
3181          to_date(NULL) exch_date,      /* exchange_date */
3182          to_number('') exch_rate,    /* exchange_rate */
3183          ps.due_date due_date,
3184          ra.apply_date apply_date,
3185          to_number('') movement_id,    /* movement_id */
3186          '' vendor_return_code,    /* tax_vendor_return_code */
3187          '' tax_auth_tax_rate,      /* tax_authority_tax_rates */
3188          '' tax_exempt_flag,      /* tax_exemption_flag */
3189          to_number('') tax_exemption_id,  /* tax_exemption_id */
3190          '' exemption_type,      /* exemption_type */
3191          '' tax_exemption_reason,              /* exemption_reason */
3192          '' tax_exemption_number,    /* customer_exemption_number */
3193          '' item_exception_rate,    /* item_exception_rate */
3194          '' meaning,                    /* item_exception_reason */
3195          '',                             /* original_collectibility_flag */
3196          '',                             /* line_collectible_flag */
3197          '',                             /* manual_override_flag */
3198          '',                             /* contingency_code */
3199          to_date(null),                  /* expiration_date */
3200          to_number(null),                /* expiration_days */
3201    ''       /* override_auto_accounting_flag */
3202          FROM
3203          ra_cust_trx_types ctt,
3204          ar_payment_schedules ps,
3205          ar_cash_receipts  cr,
3206          ar_receivable_applications ra,
3207          ra_customer_trx   ct
3208          WHERE   ctt.cust_trx_type_id    = ct.cust_trx_type_id
3209          and   ps.payment_schedule_id (+) = ra.applied_payment_schedule_id
3210          and   cr.cash_receipt_id     = ra.cash_receipt_id
3211          and   ra.applied_customer_trx_id = ct.customer_trx_id
3212          and    exists ( SELECT 'x'
3213                          FROM   ar_receivable_applications ra1
3214                          WHERE  ra1.applied_customer_trx_id = cp_customer_trx_id
3215                          AND    ra1.cash_Receipt_id = ra.cash_receipt_id )
3216         -- bug3567865 Don't insert duplicate cash record.
3217         and    not exists (
3218                   select 'already purged'
3219                     from ar_archive_detail aad
3220                    where aad.transaction_id = cr.cash_receipt_id
3221                      and aad.transaction_class = 'CASH' )
3222          UNION ALL /* Bug 5105156 - fix 5044763 */
3223          ---------------------------------------------------------------------
3224          -- CM applications (CM_APP)
3225          -- all levels
3226          ---------------------------------------------------------------------
3227          SELECT
3228          ctt_cm.type trx_class,    /* transaction_class */
3229          ctt_cm.name trx_type,      /* transaction_type */
3230          ct_cm.customer_trx_id trx_id,   /* transaction_id */
3231          to_number('') line_id,    /* transaction_line_id */
3232          ctt_inv.type related_trx_class,  /* related_transaction_class */
3233          ctt_inv.name related_trx_type,  /* related_transaction_type */
3234          ct_inv.customer_trx_id related_trx_id,/* related_transaction_id */
3235          to_number('') related_trx_line_id,  /* related_transaction_line_id */
3236          to_number('') line_number,    /* line_number */
3237          'CM_APP' dist_type,       /* distribution_type */
3238          ra.application_type app_type,    /* application_type */
3239          '' line_code_meaning,     /* line_code_meaning */
3240          '' description,
3241          '' item_name,      /* item_name */
3242          to_number('') qty,    /* quantity */
3243          to_number('') selling_price,  /* unit_selling_price */
3244          '' line_type,
3245          ra.attribute_category attr_category,
3246          ra.attribute1 attr1,
3247          ra.attribute2 attr2,
3248          ra.attribute3 attr3,
3249          ra.attribute4 attr4,
3250          ra.attribute5 attr5,
3251          ra.attribute6 attr6,
3252          ra.attribute7 attr7,
3253          ra.attribute8 attr8,
3254          ra.attribute9 attr9,
3255          ra.attribute10 attr10,
3256          ra.attribute11 attr11,
3257          ra.attribute12 attr12,
3258          ra.attribute13 attr13,
3259          ra.attribute14 attr14,
3260          ra.attribute15 attr15,
3261          ra.amount_applied,    /* amount */
3262          to_number('') acctd_amount,    /* acctd_amount */
3263          '' uom_code,
3264          '' ussgl_trx_code,
3265          to_number('') tax_rate,      /* tax_rate */
3266          '' tax_code,        /* tax_code */
3267          to_number('') tax_precedence,      /* tax_precedence */
3268          ra.code_combination_id ccid1,    /* account_ccid1 */
3269          to_number('') ccid2,        /* account_ccid2 */
3270          ra.unearned_discount_ccid ccid3, /* account_ccid3 */
3271          ra.earned_discount_ccid ccid4,
3272          ra.gl_date gl_date,
3273          ra.gl_posted_date gl_posted_date,
3274          '' rule_name,             /* acct_rule_name */
3275          to_number('') acctg_rule_duration,  /* rule_duration */
3276          to_date(NULL) rule_start_date,    /* rule_start_date */
3277          to_number('') last_period_to_credit,   /* last_period_to_credit */
3278          ra.comments line_comment,     /* line_comment */
3279          to_number('') line_adjusted,    /* line_adjusted */
3280          to_number('') freight_adjusted,  /* freight_adjusted */
3281          to_number('') tax_adjusted,    /* tax_adjusted */
3282          to_number('') charges_adjusted,  /* receivables_charges_adjusted */
3283          ra.line_applied line_applied,    /* line_applied */
3284          ra.freight_applied freight_applied,  /* freight_applied */
3285          ra.tax_applied tax_applied,    /* tax_applied */
3286          ra.receivables_charges_applied charges_applied,    /* receivables_charges_applied */
3287          ra.earned_discount_taken earned_disc_taken,       /* earned_discount_taken */
3288          ra.unearned_discount_taken unearned_disc_taken,    /* unearned_discount_taken */
3289          ra.acctd_amount_applied_from acctd_amount_applied_from,
3290                 /* acctd_amount_applied_from */
3291          ra.acctd_amount_applied_to acctd_amount_applied_to,
3292                 /* acctd_amount_applied_to */
3293          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
3294                 /* acctd_earned_disc_taken */
3295          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
3296                 /* acctd_unearned_disc_taken */
3297          to_number('') factor_discount_amount,    /* factor_discount_amount */
3298          to_number('') acctd_factor_discount_amount,  /* acctd_factor_discount_amount */
3299          '' int_line_context,    /* interface_line_context */
3300          '' int_line_attr1,        /* interface_line_attribute1 */
3301          '' int_line_attr2,        /* interface_line_attribute2 */
3302          '' int_line_attr3,        /* interface_line_attribute3 */
3303          '' int_line_attr4,        /* interface_line_attribute4 */
3304          '' int_line_attr5,        /* interface_line_attribute5 */
3305          '' int_line_attr6,        /* interface_line_attribute6 */
3306          '' int_line_attr7,        /* interface_line_attribute7 */
3307          '' int_line_attr8,        /* interface_line_attribute8 */
3308          '' int_line_attr9,        /* interface_line_attribute9 */
3309          '' int_line_attr10,        /* interface_line_attribute10 */
3310          '' int_line_attr11,        /* interface_line_attribute11 */
3311          '' int_line_attr12,        /* interface_line_attribute12 */
3312          '' int_line_attr13,        /* interface_line_attribute13 */
3313          '' int_line_attr14,        /* interface_line_attribute14 */
3314          '' int_line_attr15,        /* interface_line_attribute15 */
3315          '' exch_rate_type,         /* exchange_rate_type */
3316          to_date(NULL) exch_date,      /* exchange_rate_date */
3317          to_number('') exch_rate,    /* exchange_rate */
3318          to_date(NULL) due_date,     /* due_date */
3319          ra.apply_date apply_date,
3320          to_number('') movement_id,    /* movement_id */
3321          '' vendor_return_code,     /* tax_vendor_return_code */
3322          '' tax_auth_tax_rate,      /* tax_authority_tax_rates */
3323          '' tax_exempt_flag,      /* tax_exemption_flag */
3324          to_number('') tax_exemption_id,  /* tax_exemption_id */
3325          '' exemption_type,       /* exemption_type */
3326          '' tax_exemption_reason,    /* reason_code */
3327          '' tax_exemption_number,    /* customer_exemption_number */
3328          '' item_exception_rate,     /* item_exception_rate */
3329          '' meaning ,        /* item_exception_reason */
3330          '',                             /* original_collectibility_flag */
3331          '',                             /* line_collectible_flag */
3332          '',                             /* manual_override_flag */
3333          '',                             /* contingency_code */
3334          to_date(null),                  /* expiration_date */
3335          to_number(null),                /* expiration_days */
3336    ''       /* override_auto_accounting_flag */
3337          FROM
3338          ra_cust_trx_types ctt_cm,
3339          ra_customer_trx   ct_cm,
3340          ra_cust_trx_types ctt_inv,
3341          ar_receivable_applications ra,
3342          ra_customer_trx   ct_inv
3343          WHERE ctt_cm.cust_trx_type_id = ct_cm.cust_trx_type_id
3344          AND   ra.applied_customer_trx_id = ct_inv.customer_trx_id
3345          AND   ra.customer_trx_id = ct_cm.customer_trx_id
3346          -- bug3948805 removed
3347          -- AND   ct_cm.previous_customer_trx_id = ct_inv.customer_trx_id
3348          AND   ctt_inv.cust_trx_type_id = ct_inv.cust_trx_type_id
3349          AND   ctt_inv.type <> 'CM'
3350          -- bug3948805 added condition for ct_cm.customer_trx_id
3351          AND   ( ct_inv.customer_trx_id = cp_customer_trx_id
3352                  or   ct_cm.customer_trx_id = cp_customer_trx_id )
3353 
3354          UNION ALL /* Bug 5105156 - fix 5073245 starts */
3355          ---------------------------------------------------------------------
3356          -- REC_WRITE_OFFs
3357          -- all write-offs pertaining to receipts of the invoices
3358          ---------------------------------------------------------------------
3359          SELECT
3360          cr.type trx_class,                     /* transaction_class */
3361          '' trx_type,                           /* transaction_type */
3362          cr.cash_receipt_id trx_id,             /* transaction_id */
3363          to_number('') line_id,                 /* transaction_line_id */
3364          'Activity' related_trx_class,                    /* related_transaction_class */
3365          'Write_Off' related_trx_type,                     /* related_transaction_type */
3366          to_number('') related_trx_id,             /* related_transaction_id */
3367          to_number('') related_trx_line_id,                     /* related_transaction_line_id */
3368          to_number('') line_number,                     /* line_number */
3369          'REC_APP' dist_type,                   /* distribution_type */
3370          ra.application_type app_type,          /* application_type */
3371          '' line_code_meaning,                          /* line_code_meaning */
3372          '' description,                                /* description */
3373          '' item_name,                          /* item_name */
3374          to_number('') qty,                     /* quantity */
3375          to_number('') selling_price,                   /* unit_selling_price */
3376          '' line_type,                          /* line_type */
3377          ra.attribute_category attr_category,
3378          ra.attribute1 attr1,
3379          ra.attribute2 attr2,
3380          ra.attribute3 attr3,
3381          ra.attribute4 attr4,
3382          ra.attribute5 attr5,
3383          ra.attribute6 attr6,
3384          ra.attribute7 attr7,
3385          ra.attribute8 attr8,
3386          ra.attribute9 attr9,
3387          ra.attribute10 attr10,
3388          ra.attribute11 attr11,
3389          ra.attribute12 attr12,
3390          ra.attribute13 attr13,
3391          ra.attribute14 attr14,
3392          ra.attribute15 attr15,
3393          ra.amount_applied amount, /* amount */
3394          to_number('') acctd_amount,                    /* acctd_amount */
3395          '' uom_code,                                   /* uom code */
3396          cr.ussgl_transaction_code ussgl_trx_code,
3397          to_number('') tax_rate,                /* tax_rate */
3398          '' tax_code,                           /* tax_code */
3399          to_number('') tax_precedence,                  /* tax_precedence */
3400          ra.code_combination_id ccid1,    /* account_ccid1 */
3401          to_number('') ccid2,              /* account_ccid2 */
3402          ra.earned_discount_ccid ccid3,   /* account_ccid3 */
3403          ra.unearned_discount_ccid ccid4, /* account_ccid4 */
3404          ra.gl_date gl_date,
3405          ra.gl_posted_date gl_posted_date,
3406          '' rule_name,              /* acct_rule_name */
3407          to_number('') acctg_rule_duration,/* rule_duration */
3408          to_date(NULL) rule_start_date,     /* rule_start_date */
3409          to_number('') last_period_to_credit,  /* last_period_to_credit */
3410          ra.comments line_comment,              /* line_comment */
3411          to_number('') line_adjusted,           /* line_adjusted */
3412          to_number('') freight_adjusted,        /* freight_adjusted */
3413          to_number('') tax_adjusted,            /* tax_adjusted */
3414          to_number('') charges_adjusted,        /* receivables_charges_adjusted */
3415          ra.line_applied line_applied,          /* line_applied */
3416          ra.freight_applied freight_applied,    /* freight_applied */
3417          ra.tax_applied tax_applied,            /* tax_applied */
3418          ra.receivables_charges_applied charges_applied,/* receivables_charges_applied */
3419          ra.earned_discount_taken earned_disc_taken,     /* earned_discount_taken */
3420          ra.unearned_discount_taken unearned_disc_taken,/* unearned_discount_taken */
3421          ra.acctd_amount_applied_from acctd_amount_applied_from,
3422                 /* acctd_amount_applied_from */
3423          ra.acctd_amount_applied_to acctd_amount_applied_to,
3424                 /* acctd_amount_applied_to */
3425          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
3426                 /* acctd_earned_disc_taken */
3427          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
3428                 /* acctd_unearned_disc_taken */
3429          to_number('') factor_discount_amount,  /* factor_discount_amount */
3430          to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
3431          '' int_line_context,                   /* interface_line_context */
3432          '' int_line_attr1,                     /* interface_line_attribute1 */
3433          '' int_line_attr2,                     /* interface_line_attribute2 */
3434          '' int_line_attr3,                     /* interface_line_attribute3 */
3435          '' int_line_attr4,                     /* interface_line_attribute4 */
3436          '' int_line_attr5,                     /* interface_line_attribute5 */
3437          '' int_line_attr6,                     /* interface_line_attribute6 */
3438          '' int_line_attr7,                     /* interface_line_attribute7 */
3439          '' int_line_attr8,                     /* interface_line_attribute8 */
3440          '' int_line_attr9,                     /* interface_line_attribute9 */
3441          '' int_line_attr10,            /* interface_line_attribute10 */
3442          '' int_line_attr11,            /* interface_line_attribute11 */
3443          '' int_line_attr12,                    /* interface_line_attribute12 */
3444          '' int_line_attr13,                    /* interface_line_attribute13 */
3445          '' int_line_attr14,                    /* interface_line_attribute14 */
3446          '' int_line_attr15,                    /* interface_line_attribute15 */
3447          '' exch_rate_type,                     /* exchange_rate_type */
3448          to_date(NULL) exch_date,               /* exchange_date */
3449          to_number('') exch_rate,               /* exchange_rate */
3450          to_date(NULL) due_date,
3451          ra.apply_date apply_date,
3452          to_number('') movement_id,             /* movement_id */
3453          '' vendor_return_code,         /* tax_vendor_return_code */
3454          '' tax_auth_tax_rate,                  /* tax_authority_tax_rates */
3455          '' tax_exempt_flag,                    /* tax_exemption_flag */
3456          to_number('') tax_exemption_id,        /* tax_exemption_id */
3457          '' exemption_type,                     /* exemption_type */
3458          '' tax_exemption_reason,              /* exemption_reason */
3459          '' tax_exemption_number,               /* customer_exemption_number */
3460          '' item_exception_rate,                /* item_exception_rate */
3461          '' meaning,                            /* item_exception_reason */
3462          '',                             /* original_collectibility_flag */
3463          '',                             /* line_collectible_flag */
3464          '',                             /* manual_override_flag */
3465          '',                             /* contingency_code */
3466          to_date(null),                  /* expiration_date */
3467          to_number(null),                /* expiration_days */
3468          ''                      /* override_auto_accounting_flag */
3469          FROM
3470          ar_cash_receipts  cr,
3471          ar_receivable_applications ra
3472          where  cr.cash_receipt_id     = ra.cash_receipt_id
3473          and    ra.applied_payment_schedule_id = -3
3474          and    ra.status = 'ACTIVITY'
3475          and    ra.display = 'Y'
3476          and    ra.reversal_gl_date is null
3477          and    exists ( SELECT 'x'
3478                          FROM   ar_receivable_applications ra1
3479                          WHERE  ra1.applied_customer_trx_id =
3480                                      cp_customer_trx_id
3481                          AND    ra1.cash_Receipt_id = ra.cash_receipt_id )
3482          and    not exists (
3483                   select 'already purged'
3484                     from ar_archive_detail aad
3485                    where aad.transaction_id = cr.cash_receipt_id
3486                      and aad.transaction_class = 'CASH' );
3487 
3488          /* Bug 5105156 - fix 5073245 ends */
3489 
3490 
3491          l_org_profile VARCHAR2(30) ;
3492 
3493          l_account_combination1 VARCHAR2(240) ;
3494          l_account_combination2 VARCHAR2(240) ;
3495          l_account_combination3 VARCHAR2(240) ;
3496          l_account_combination4 VARCHAR2(240) ;
3497 
3498      BEGIN
3499 
3500 
3501          oe_profile.get('SO_ORGANIZATION_ID', l_org_profile);
3502 
3503          FOR select_detail IN detail_cursor ( p_customer_trx_id,
3504                                               p_archive_level ,
3505                                               l_org_profile )
3506          LOOP
3507 
3508              l_account_combination1 := NULL ;
3509              l_account_combination2 := NULL ;
3510              l_account_combination3 := NULL ;
3511              l_account_combination4 := NULL ;
3512              --
3513              IF select_detail.ccid1 > 0 THEN
3514                 l_account_combination1 := get_ccid(select_detail.ccid1) ;
3515              END IF ;
3516              --
3517              IF select_detail.ccid2 > 0 THEN
3518                 l_account_combination2 := get_ccid(select_detail.ccid2) ;
3519              END IF ;
3520              --
3521              IF select_detail.ccid3 > 0 THEN
3522                 l_account_combination3 := get_ccid(select_detail.ccid3) ;
3523              END IF ;
3524              --
3525              IF select_detail.ccid4 > 0 THEN
3526                 l_account_combination4 := get_ccid(select_detail.ccid4) ;
3527              END IF ;
3528              --
3529              INSERT INTO ar_archive_detail
3530              ( archive_id,
3531                transaction_class,
3532                transaction_type,
3533                transaction_id,
3534                transaction_line_id,
3535                related_transaction_class,
3536                related_transaction_type,
3537                related_transaction_id,
3538                related_transaction_line_id,
3539                line_number,
3540                distribution_type,
3541                application_type,
3542                reason_code_meaning,
3543                line_description,
3544                item_name,
3545                quantity,
3546                unit_selling_price,
3547                line_type,
3548                attribute_category,
3549                attribute1,
3550                attribute2,
3551                attribute3,
3552                attribute4,
3553                attribute5,
3554                attribute6,
3555                attribute7,
3556                attribute8,
3557                attribute9,
3558                attribute10,
3559                attribute11,
3560                attribute12,
3561                attribute13,
3562                attribute14,
3563                attribute15,
3564                amount,
3565                -- acctd_amount, -- bug1199027
3566                uom_code,
3567                ussgl_transaction_code,
3568                tax_rate,
3569                tax_code,
3570                tax_precedence,
3571                account_combination1,
3572                account_combination2,
3573                account_combination3,
3574                account_combination4,
3575                gl_date,
3576                gl_posted_date,
3577                accounting_rule_name,
3578                rule_duration,
3579                rule_start_date,
3580                last_period_to_credit,
3581                comments,
3582                line_adjusted,
3583                freight_adjusted,
3584                tax_adjusted,
3585                receivables_charges_adjusted,
3586                line_applied,
3587                freight_applied,
3588                tax_applied,
3589                receivables_charges_applied,
3590                earned_discount_taken,
3591                unearned_discount_taken,
3592                -- acctd_amount_applied_from, -- bug1199027
3593                -- acctd_amount_applied_to, -- bug1199027
3594                -- acctd_earned_disc_taken, -- bug1199027
3595                -- acctd_unearned_disc_taken, -- bug1199027
3596                factor_discount_amount,
3597                -- acctd_factor_discount_amount, -- bug1199027
3598                interface_line_context,
3599                interface_line_attribute1,
3600                interface_line_attribute2,
3601                interface_line_attribute3,
3602                interface_line_attribute4,
3603                interface_line_attribute5,
3604                interface_line_attribute6,
3605                interface_line_attribute7,
3606                interface_line_attribute8,
3607                interface_line_attribute9,
3608                interface_line_attribute10,
3609                interface_line_attribute11,
3610                interface_line_attribute12,
3611                interface_line_attribute13,
3612                interface_line_attribute14,
3613                interface_line_attribute15,
3614                exchange_rate_type,
3615                exchange_rate_date,
3616                exchange_rate,
3617                due_date,
3618                apply_date,
3619                movement_id,
3620                tax_vendor_return_code,
3621                tax_authority_tax_rates,
3622                tax_exemption_flag,
3623                tax_exemption_id,
3624                tax_exemption_type,
3625                tax_exemption_reason,
3626                tax_exemption_number,
3627                item_exception_rate,
3628                Item_exception_reason ,
3629                original_collectibility_flag,
3630                line_collectible_flag,
3631                manual_override_flag,
3632                contingency_code,
3633                expiration_date,
3634                expiration_days,
3635          override_auto_accounting_flag
3636              )
3637              VALUES
3638              ( lpad(p_archive_id,14,'0'), /* modified for bug 3266428 */
3639                select_detail.trx_class,
3640                select_detail.trx_type,
3641                select_detail.trx_id,
3642                select_detail.line_id,
3643                select_detail.related_trx_class,
3644                select_detail.related_trx_type,
3645                select_detail.related_trx_id,
3646                select_detail.related_trx_line_id,
3647                select_detail.line_number,
3648                select_detail.dist_type,
3649                select_detail.app_type,
3650                select_detail.line_code_meaning,
3651                select_detail.description,
3652                select_detail.item_name,
3653                select_detail.qty,
3654                select_detail.selling_price,
3655                select_detail.line_type,
3656                select_detail.attr_category,
3657                select_detail.attr1,
3658                select_detail.attr2,
3659                select_detail.attr3,
3660                select_detail.attr4,
3661                select_detail.attr5,
3662                select_detail.attr6,
3663                select_detail.attr7,
3664                select_detail.attr8,
3665                select_detail.attr9,
3666                select_detail.attr10,
3667                select_detail.attr11,
3668                select_detail.attr12,
3669                select_detail.attr13,
3670                select_detail.attr14,
3671                select_detail.attr15,
3672                select_detail.amount,
3673                -- select_detail.acctd_amount, -- bug1199027
3674                select_detail.uom_code,
3675                select_detail.ussgl_trx_code,
3676                select_detail.tax_rate,
3677                select_detail.tax_code,
3678                select_detail.tax_precedence,
3679                l_account_combination1,
3680                l_account_combination2,
3681                l_account_combination3,
3682                l_account_combination4,
3683                select_detail.gl_date,
3684                select_detail.gl_posted_date,
3685                select_detail.rule_name,
3686                select_detail.acctg_rule_duration,
3687                select_detail.rule_start_date,
3688                select_detail.last_period_to_credit,
3689                select_detail.line_comment,
3690                select_detail.line_adjusted,
3691                select_detail.freight_adjusted,
3692                select_detail.tax_adjusted,
3693                select_detail.charges_adjusted,
3694                select_detail.line_applied,
3695                select_detail.freight_applied,
3696                select_detail.tax_applied,
3697                select_detail.charges_applied,
3698                select_detail.earned_disc_taken,
3699                select_detail.unearned_disc_taken,
3700                -- select_detail.acctd_amount_applied_from, -- bug1199027
3701                -- select_detail.acctd_amount_applied_to, -- bug1199027
3702                -- select_detail.acctd_earned_disc_taken, -- bug1199027
3703                -- select_detail.acctd_unearned_disc_taken, -- bug1199027
3704                select_detail.factor_discount_amount,
3705                -- select_detail.acctd_factor_discount_amount, -- bug1199027
3706                select_detail.int_line_context,
3707                select_detail.int_line_attr1,
3708                select_detail.int_line_attr2,
3709                select_detail.int_line_attr3,
3710                select_detail.int_line_attr4,
3711                select_detail.int_line_attr5,
3712                select_detail.int_line_attr6,
3713                select_detail.int_line_attr7,
3714                select_detail.int_line_attr8,
3715                select_detail.int_line_attr9,
3716                select_detail.int_line_attr10,
3717                select_detail.int_line_attr11,
3718                select_detail.int_line_attr12,
3719                select_detail.int_line_attr13,
3720                select_detail.int_line_attr14,
3721                select_detail.int_line_attr15,
3722                select_detail.exch_rate_type,
3723                select_detail.exch_date,
3724                select_detail.exch_rate,
3725                select_detail.due_date,
3726                select_detail.apply_date,
3727                select_detail.movement_id,
3728                select_detail.vendor_return_code,
3729                select_detail.tax_auth_tax_rate,
3730                select_detail.tax_exempt_flag,
3731                select_detail.tax_exemption_id,
3732                select_detail.exemption_type,
3733                select_detail.tax_exemption_reason,
3734                select_detail.tax_exemption_number,
3735                select_detail.item_exception_rate,
3736                select_detail.meaning,
3737                select_detail.original_collectibility_flag,
3738                select_detail.line_collectible_flag,
3739                select_detail.manual_override_flag,
3740                select_detail.contingency_code,
3741                select_detail.expiration_date,
3742                select_detail.expiration_days,
3743          select_detail.override_auto_accounting_flag
3744              ) ;
3745 
3746          END LOOP ;
3747 
3748          RETURN TRUE ;
3749 
3750     EXCEPTION
3751         WHEN OTHERS THEN
3752             print( 1, '  ...Failed while inserting into AR_ARCHIVE_DETAIL');
3753             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3754             RAISE ;
3755     END;
3756     --
3757     -- archive - Processing Cycle
3758     --
3759     PROCEDURE archive( p_archive_id IN NUMBER,
3760                        p_customer_trx_id IN NUMBER,
3761                        p_archive_level IN VARCHAR2,
3762                        p_archive_status OUT NOCOPY BOOLEAN  ) IS
3763         l_error_location VARCHAR2(50) ;
3764         h boolean ;
3765     BEGIN
3766 
3767         -- bug3975105 add 'N'
3768         print( 1, '...archiving ', 'N');
3769         l_error_location := 'archive_header' ;
3770 
3771         IF archive_header( p_customer_trx_id ,
3772                            p_archive_id      ) = FALSE
3773         THEN
3774             print( 0, '  ...Failed while inserting into AR_ARCHIVE_HEADER ');
3775             p_archive_status := FALSE ;
3776         END IF ;
3777 
3778         l_error_location := 'archive_detail' ;
3779         IF  archive_detail( p_customer_trx_id  ,
3780                             p_archive_level    ,
3781                             p_archive_id       ) = FALSE
3782         THEN
3783             print( 0, '  ...Failed while inserting into AR_ARCHIVE_DETAIL ');
3784             p_archive_status := FALSE ;
3785         ELSE
3786             p_archive_status := TRUE ;
3787         END IF ;
3788 
3789     EXCEPTION
3790         WHEN OTHERS THEN
3791             print( 0, l_error_location ) ;
3792             print( 0, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3793             print( 0, '  ...Archive Failed ');
3794             p_archive_status := FALSE ;
3795             RAISE ;
3796     END;
3797     --
3798     --
3799     -- returns TRUE if the entity was successfully purged
3800     -- returns FALSE otherwise
3801     --
3802     FUNCTION recursive_purge( p_entity_id       IN     NUMBER,
3803                               p_entity_type     IN     VARCHAR2,
3804                               p_as_of_gl_date   IN     DATE,
3805                               p_customer_id     IN     NUMBER,
3806                               p_archive_level   IN     VARCHAR2,
3807                               p_recursive_level IN     NUMBER,
3808                               p_running_total   IN OUT NOCOPY NUMBER ) RETURN BOOLEAN
3809     IS
3810         l_dummy          NUMBER;
3811         l_archive_status BOOLEAN ;
3812 
3813     BEGIN
3814         -- bug3975105 added 'Y'
3815         print( p_recursive_level, 'Processing id:'||p_entity_id||' type:'||p_entity_type|| ' at ' || to_char(sysdate,'dd-mon-yyyy hh:mi:ss'), 'Y');
3816 
3817         IF p_entity_type = 'CT'
3818         THEN
3819             IF in_unpurgeable_txn_list( p_entity_id )
3820             THEN
3821                 -- bug3975105 added 'S'
3822                 print( p_recursive_level, '  ...already in unpurgeable transaction list', 'S');
3823                 RETURN FALSE;
3824             END IF;
3825             --
3826             IF trx_purgeable ( p_entity_id ) = FALSE
3827             THEN
3828                 print( p_recursive_level, '  ...is unpurgeable due to customisation' ) ;
3829                 RETURN FALSE;
3830             END IF ;
3831             --
3832             DECLARE
3833                 l_record_found  VARCHAR2(10) := 'Not Found' ;
3834 
3835                 /* bug1999155: Divided select stmt which lock all transactions
3836                   records into the following stmts */
3837                 cursor trx_cur is
3838                     SELECT  'Found'  record_found
3839                     from    ra_customer_trx trx
3840                     WHERE   trx.customer_trx_id = p_entity_id
3841                     FOR     UPDATE OF trx.customer_trx_id NOWAIT;
3842 
3843                 cursor trx_line_cur is
3844                     SELECT  'Found'  record_found
3845                     from    ra_customer_trx_lines lines
3846                     WHERE   lines.customer_trx_id = p_entity_id
3847                     FOR     UPDATE OF lines.customer_trx_id NOWAIT;
3848 
3849                 cursor dist_cur is
3850                     SELECT  'Found'  record_found
3851                     from    ra_cust_trx_line_gl_dist dist
3852                     WHERE   dist.customer_trx_id = p_entity_id
3853                     FOR     UPDATE OF dist.customer_trx_id NOWAIT;
3854 
3855                 cursor sales_cur is
3856                     SELECT  'Found'  record_found
3857                     from    ra_cust_trx_line_salesreps sales
3858                     WHERE   sales.customer_trx_id = p_entity_id
3859                     FOR     UPDATE OF sales.customer_trx_id NOWAIT;
3860 
3861                 cursor adj_cur is
3862                     SELECT  'Found'  record_found
3863                     from    ar_adjustments adj
3864                     WHERE   adj.customer_trx_id  = p_entity_id
3865                     FOR     UPDATE OF adj.customer_trx_id NOWAIT;
3866 
3867                 cursor recv_app_cur is
3868                     SELECT  'Found'  record_found
3869                     from    ar_receivable_applications ra
3870                     WHERE   ra.applied_customer_trx_id = p_entity_id
3871                     FOR     UPDATE OF ra.customer_trx_id NOWAIT;
3872 
3873                 cursor pay_sched_cur is
3874                     SELECT  'Found'  record_found
3875                     from    ar_payment_schedules ps
3876                     WHERE   ps.customer_trx_id = p_entity_id
3877                     FOR     UPDATE OF ps.customer_trx_id NOWAIT;
3878 
3879             BEGIN
3880                 -- lock all the transaction records
3881                 /* bug1999155: Divided the following select stmt into
3882                   some stmts. This cursor for loop is not used .
3883                 FOR lock_rec IN (
3884                                   SELECT 'Found'  record_found
3885                                   FROM   ra_cust_trx_line_salesreps sales,
3886                                          ar_receivable_applications ra,
3887                                          ar_payment_schedules ps,
3888                                          ar_adjustments adj,
3889                                          ra_cust_trx_line_gl_dist dist,
3890                                          ra_customer_trx_lines lines,
3891                                          ra_customer_trx trx
3892                                   WHERE  trx.customer_trx_id = p_entity_id
3893                                   AND    trx.customer_trx_id = lines.customer_trx_id
3894                                   AND    trx.customer_trx_id = dist.customer_trx_id (+)
3895                                   AND    trx.customer_trx_id = sales.customer_trx_id (+)
3896                                   AND    trx.customer_trx_id = adj.customer_trx_id (+)
3897                                   AND    trx.customer_trx_id = ra.applied_customer_trx_id (+)
3898                                   AND    trx.customer_trx_id = ps.customer_trx_id (+)
3899                                   FOR    UPDATE OF trx.customer_trx_id ,
3900                                                    lines.customer_trx_id,
3901                                                    dist.customer_trx_id,
3902                                                    sales.customer_trx_id,
3903                                                    adj.customer_trx_id,
3904                                                    ra.customer_trx_id,
3905                                                    ps.customer_trx_id NOWAIT
3906                                )
3907                 LOOP
3908                     l_record_found := lock_rec.record_found ;
3909                 END LOOP ;
3910                 bug1999155 end */
3911 
3912                 /* bug1999155 : Open created cursors to lock */
3913                 open    trx_cur;
3914 
3915                 fetch  trx_cur
3916                 into l_record_found;
3917 
3918                 -- Need to verify if NO_DATA_FOUND will be raised if
3919                 -- the cursor does not return any row.
3920                 --
3921                 IF l_record_found = 'Not Found'
3922                 THEN
3923                    RETURN TRUE ; -- No Data Found
3924                 END IF ;
3925 
3926                 close   trx_cur;
3927 
3928                 open    trx_line_cur;
3929                 close   trx_line_cur;
3930 
3931                 open    dist_cur;
3932                 close   dist_cur;
3933 
3934                 open    sales_cur;
3935                 close   sales_cur;
3936 
3937                 open    adj_cur;
3938                 close   adj_cur;
3939 
3940                 open    recv_app_cur;
3941                 close   recv_app_cur;
3942 
3943                 open    pay_sched_cur;
3944                 close   pay_sched_cur;
3945 
3946             EXCEPTION
3947                 WHEN NO_DATA_FOUND THEN
3948                     RETURN TRUE; -- assume already processed in this thread
3949                 WHEN locked_by_another_session THEN
3950                     print( p_recursive_level, ' ...locked by another session' );
3951                     RETURN FALSE; -- assume already processed in this thread
3952                 WHEN OTHERS THEN
3953                     print( p_recursive_level, ' ...Failed while trying to lock' );
3954                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3955                     RAISE;
3956             END;
3957 
3958 
3959             /* Bug2472294 : Merged following condition into next one.
3960             --
3961             -- ensure that the transaction is neither a commitment nor
3962             -- related to a commitment
3963             --
3964             DECLARE
3965                 l_commitment_transactions NUMBER;
3966             BEGIN
3967                 SELECT  COUNT(*)
3968                 INTO    l_commitment_transactions
3969                 FROM    ra_customer_trx     ct,
3970                         ra_cust_trx_types   ctt
3971                 WHERE   ct.customer_trx_id = p_entity_id
3972                 AND     ctt.cust_trx_type_id = ct.cust_trx_type_id
3973                 AND
3974                 (
3975                     ctt.type IN ( 'GUAR', 'DEP' )   OR
3976                     ct.initial_customer_trx_id IS NOT NULL
3977                 );
3978                 --
3979                 IF l_commitment_transactions > 0
3980                 THEN
3981                     print( p_recursive_level, '  ...is a commitment or related to a commitment');
3982                     RETURN FALSE;
3983                 END IF;
3984             END;
3985             Bug 2472294 */
3986 
3987 
3988             -- bug2472294 start
3989             -- Handle non post to gl transaction
3990             DECLARE
3991                 l_type ra_cust_trx_types.type%TYPE ;
3992                 l_initial_customer_trx_id ra_customer_trx.initial_customer_trx_id%TYPE;
3993                 l_post_to_gl ra_cust_trx_types.post_to_gl%TYPE;
3994                 l_trx_date ra_customer_trx.trx_date%TYPE;
3995 
3996             BEGIN
3997 
3998                 SELECT  ctt.type,
3999                         ct.initial_customer_trx_id,
4000                         ctt.post_to_gl,
4001                         ct.trx_date
4002                 INTO    l_type,
4003                         l_initial_customer_trx_id,
4004                         l_post_to_gl,
4005                         l_trx_date
4006                 FROM    ra_customer_trx ct,
4007                         ra_cust_trx_types ctt
4008                 WHERE   ct.customer_trx_id = p_entity_id
4009                 AND     ctt.cust_trx_type_id = ct.cust_trx_type_id ;
4010 
4011                 --
4012                 -- ensure that the transaction is neither a commitment nor
4013                 -- related to a commitment
4014                 --
4015                 IF ( l_type = 'GUAR' ) or ( l_type = 'DEP') or
4016                 ( l_initial_customer_trx_id IS NOT NULL )
4017                 THEN
4018                    print( p_recursive_level, '  ...is a commitment or related to a commitment') ;
4019                    RETURN FALSE;
4020                 END IF;
4021 
4022                 IF l_post_to_gl = 'Y'
4023                 THEN
4024                    --
4025                    -- select distributions that are unposted or whose gl_date
4026                    -- is after the purge date
4027                    --
4028                    DECLARE
4029                       l_unpurgeable_distributions   NUMBER;
4030                    BEGIN
4031                       SELECT  COUNT(*)
4032                       INTO    l_unpurgeable_distributions
4033                       FROM    ra_cust_trx_line_gl_dist
4034                       WHERE   customer_trx_id = p_entity_id
4035                       AND     account_set_flag = 'N'
4036                       AND
4037                       (
4038                           posting_control_id = -3    OR
4039                           gl_date > p_as_of_gl_date
4040                       );
4041                       IF l_unpurgeable_distributions <> 0 THEN
4042                          print( p_recursive_level, '  ...which has unpurgeable distributions' );
4043                          RETURN FALSE;
4044                       END IF;
4045                       ---
4046                       ---
4047                    END;
4048                    --
4049                    -- check for adjustments that violate rules
4050                    --    (NOTE: unapproved adjustments are excluded from search)
4051                    --           It is most unlikely that these unapproved adjs.
4052                    --           will be approved. So, these need not be
4053                    --           considered.
4054                    --
4055                    DECLARE
4056                       l_violate_adjustments   NUMBER;
4057                    BEGIN
4058                       SELECT  COUNT(*)
4059                       INTO    l_violate_adjustments
4060                       FROM    ar_adjustments
4061                       WHERE   customer_trx_id = p_entity_id
4062                       AND     status in ('A', 'M', 'W') -- bug1999155
4063                       AND
4064                       (
4065                           posting_control_id = -3    OR
4066                           gl_date            > p_as_of_gl_date
4067                       );
4068                       IF l_violate_adjustments > 0
4069                       THEN
4070                          print( p_recursive_level, '  ...unpurgeable adjustments' );
4071                          RETURN FALSE;
4072                       END IF;
4073                    END;
4074 
4075                 /* l_post_to_gl = 'N'  */
4076                 ELSE
4077 
4078                    IF l_trx_date > p_as_of_gl_date
4079                    THEN
4080                       print( p_recursive_level, '  ...transaction date is after the purge date');
4081                       RETURN FALSE;
4082                    END IF;
4083 
4084                    --
4085                    -- check for adjustments that violate rules
4086                    --    (NOTE: unapproved adjustments are excluded from search)
4087                    --           It is most unlikely that these unapproved adjs.
4088                    --           will be approved. So, these need not be
4089                    --           considered.
4090                    --
4091                    DECLARE
4092                       l_violate_adjustments   NUMBER;
4093                    BEGIN
4094                       SELECT  COUNT(*)
4095                       INTO    l_violate_adjustments
4096                       FROM    ar_adjustments
4097                       WHERE   customer_trx_id = p_entity_id
4098                       AND     status in ('A', 'M', 'W')
4099                       AND decode ( status, 'A', gl_date , p_as_of_gl_date + 1)
4100                              > p_as_of_gl_date ;
4101 
4102                       IF l_violate_adjustments > 0
4103                       THEN
4104                          print( p_recursive_level, '  ...unpurgeable adjustments' );
4105                          RETURN FALSE;
4106                       END IF;
4107                    END;
4108                 END IF;
4109 
4110             EXCEPTION
4111                 WHEN OTHERS THEN
4112                 print( 1, 'Failed while checking the Transaction Type');
4113                 print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4114                 RAISE ;
4115             END ;
4116             -- bug2472294 end
4117 
4118 
4119             --
4120             --
4121             -- Check if this trx. belongs to the same customer
4122             --
4123             DECLARE
4124                 l_same_customer   VARCHAR2(1);
4125             BEGIN
4126 
4127                 IF p_customer_id IS NOT NULL THEN
4128 
4129                    BEGIN
4130                        SELECT  'Y'
4131                        INTO    l_same_customer
4132                        FROM    ra_customer_trx
4133                        WHERE   customer_trx_id = p_entity_id
4134                        AND     bill_to_customer_id = p_customer_id ;
4135 
4136                    EXCEPTION
4137                        WHEN NO_DATA_FOUND THEN
4138                            print( p_recursive_level, '  ...Bill to Customer is different' );
4139                            RETURN FALSE ;
4140                        WHEN OTHERS THEN
4141                            RAISE ;
4142                    END ;
4143                 END IF ;
4144                 --
4145             END;
4146             --
4147             -- check that all of the invoice's payment schedules are closed
4148             --
4149             DECLARE
4150                 l_invoice_open_amount   NUMBER;
4151             BEGIN
4152                 SELECT  NVL(SUM(ABS(amount_due_remaining)),0)
4153                 INTO    l_invoice_open_amount
4154                 FROM    ar_payment_schedules
4155                 WHERE   customer_trx_id = p_entity_id;
4156                 --
4157                 IF l_invoice_open_amount > 0 THEN
4158                     print( p_recursive_level, '  ...payment schedule is not closed' );
4159                     RETURN FALSE;
4160                 END IF;
4161                 --
4162             EXCEPTION
4163                 WHEN OTHERS THEN
4164                     print( 1, 'Failed while checking the Payment Schedules');
4165                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4166                     RAISE ;
4167             END;
4168             --
4169             -- ensure that autorule is complete for this transaction
4170             --
4171             DECLARE
4172                 l_autorule_incomplete_count    NUMBER;
4173             BEGIN
4174                 SELECT  COUNT(*)
4175                 INTO    l_autorule_incomplete_count
4176                 FROM    ra_customer_trx_lines
4177                 WHERE   customer_trx_id        = p_entity_id
4178                 AND     line_type              = 'LINE'
4179                 AND     autorule_complete_flag = 'N';
4180                 IF l_autorule_incomplete_count > 0
4181                 THEN
4182                     print( p_recursive_level, '  ...autorule is not complete' );
4183                     RETURN FALSE;
4184                 END IF;
4185             END;
4186 
4187             /* bug2472294 : Moved to above because this was executed only when
4188                post_to_gl is 'Y'.
4189             --
4190             -- select distributions that are unposted or whose gl_date
4191             -- is after the purge date
4192             --
4193             DECLARE
4194                 l_unpurgeable_distributions   NUMBER;
4195             BEGIN
4196                 SELECT  COUNT(*)
4197                 INTO    l_unpurgeable_distributions
4198                 FROM    ra_cust_trx_line_gl_dist
4199                 WHERE   customer_trx_id = p_entity_id
4200                 AND     account_set_flag = 'N'
4201                 AND
4202                 (
4203                     posting_control_id = -3    OR
4204                     gl_date > p_as_of_gl_date
4205                 );
4206                 IF l_unpurgeable_distributions <> 0 THEN
4207                     print( p_recursive_level, '  ...which has unpurgeable distributions' );
4208                     RETURN FALSE;
4209                 END IF;
4210                 ---
4211                 ---
4212             END;
4213             --
4214             -- check for adjustments that violate rules
4215             --    (NOTE: unapproved adjustments are excluded from search)
4216             --           It is most unlikely that these unapproved adjs.
4217             --           will be approved. So, these need not be
4218             --           considered.
4219             --
4220 
4221             DECLARE
4222                 l_violate_adjustments   NUMBER;
4223             BEGIN
4224                 SELECT  COUNT(*)
4225                 INTO    l_violate_adjustments
4226                 FROM    ar_adjustments
4227                 WHERE   customer_trx_id = p_entity_id
4228                 AND     status in ('A', 'M', 'W') -- bug1999155
4229                 AND
4230                 (
4231                     posting_control_id = -3    OR
4232                     gl_date            > p_as_of_gl_date
4233                 );
4234                 IF l_violate_adjustments > 0
4235                 THEN
4236                     print( p_recursive_level, '  ...unpurgeable adjustments' );
4237                     RETURN FALSE;
4238                 END IF;
4239             END;
4240             bug2472294 */
4241 
4242             --
4243             -- Check if any applications are unpurgeable
4244             --
4245             DECLARE
4246                 l_unpurgeable_applications  NUMBER;
4247             BEGIN
4248                 SELECT  COUNT(*)
4249                 INTO    l_unpurgeable_applications
4250                 FROM    ar_receivable_applications
4251                 WHERE
4252                 (
4253                     applied_customer_trx_id = p_entity_id     OR
4254                     customer_trx_id         = p_entity_id
4255                 )
4256                 AND
4257                 (
4258                     posting_control_id = -3         OR
4259                     gl_date            > p_as_of_gl_date
4260                 )
4261                 AND postable = 'Y' ; -- bug3404430 added to check only postable
4262                 IF l_unpurgeable_applications > 0 THEN
4263                     print( p_recursive_level, '  ...unpurgeable applications' );
4264                     RETURN FALSE;
4265                 END IF;
4266             END;
4267             --
4268 
4269             DECLARE
4270                 l_receivable_amount  NUMBER ;
4271                 l_adjustment_amount  NUMBER ;
4272             BEGIN
4273 
4274                 SELECT acctd_amount
4275                 INTO   l_receivable_amount
4276                 FROM   RA_CUST_TRX_LINE_GL_DIST
4277                 WHERE  customer_trx_id = p_entity_id
4278                 AND    account_class   = 'REC'
4279                 AND    latest_rec_flag = 'Y'  ;
4280 
4281                 p_running_total := p_running_total + l_receivable_amount ;
4282 
4283                 SELECT NVL(SUM(acctd_amount),0)
4284                 INTO   l_adjustment_amount
4285                 FROM   ar_adjustments
4286                 WHERE  customer_trx_id = p_entity_id
4287                 AND    status in ('A', 'M', 'W') ;  -- bug1999155
4288 
4289                 p_running_total := p_running_total + l_adjustment_amount;
4290 
4291             EXCEPTION
4292                   /* bug1999155 No need to handle NO_DATA_FOUND error
4293                   WHEN NO_DATA_FOUND THEN
4294                       RETURN FALSE;
4295       */
4296                   WHEN OTHERS THEN
4297                       print( 1, 'Failed while checking GL_DIST/ADJ');
4298                       print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4299                       RAISE;
4300             END ;
4301             -- bug3873165 Added following check
4302             --
4303             -- check if line revenue is completed
4304             --
4305 
4306             DECLARE
4307                 l_line_revenue     NUMBER;
4308             BEGIN
4309                 SELECT  COUNT(*)
4310                 INTO    l_line_revenue
4311                 FROM    ar_deferred_lines dl
4312                 WHERE   p_entity_id = dl.customer_trx_id
4313                 AND     dl.line_collectible_flag = 'N'
4314                 AND     dl.manual_override_flag = 'N'
4315                 AND     dl.acctd_amount_due_original <> dl.acctd_amount_recognized;
4316 
4317                 IF  l_line_revenue > 0
4318                 THEN
4319                     print( p_recursive_level, '  ...line revenue is not completed ' );
4320                     RETURN FALSE;
4321                 END IF;
4322             END;
4323             --
4324             DECLARE
4325                 l_batch_id NUMBER(15) ;
4326 
4327                 /* bug2021662 : added for getting deleted correspondence_id */
4328                 TYPE Del_Cid_Tab IS TABLE OF ar_correspondences.correspondence_id%TYPE INDEX BY BINARY_INTEGER;
4329                 del_cid Del_Cid_Tab;
4330 
4331                 l_corr_row   BINARY_INTEGER := 0 ;
4332 
4333             BEGIN
4334                 --
4335                 -- Archive rows here before deleting so that
4336                 -- you don't lose the data
4337                 --
4338                 archive( l_archive_id,
4339                          p_entity_id,
4340                          p_archive_level,
4341                          l_archive_status) ;
4342 
4343                 IF l_archive_status = FALSE
4344                 THEN
4345                     print( 0,'Archive Failed') ;
4346                     RETURN ( FALSE ) ;
4347                 END IF ;
4348                 --
4349                 SELECT bat.batch_id
4350                 INTO   l_batch_id
4351                 FROM   ra_batches bat,
4352                        ra_customer_trx trx
4353                 WHERE  trx.customer_trx_id = p_entity_id
4354                 AND    trx.batch_id = bat.batch_id (+)
4355                 FOR    UPDATE OF bat.batch_id NOWAIT ;
4356                 --
4357                 -- bug3975105 added 'N'
4358                 print( p_recursive_level, '  ...deleting rows', 'N' );
4359                 --
4360                 /* bug3873165 added two tables for line rev */
4361                 DELETE FROM ar_line_conts
4362                 WHERE  customer_trx_line_id in ( select customer_trx_line_id
4363                                       from   ra_customer_trx
4364                                       where  customer_trx_id = p_entity_id );
4365                 --
4366                 DELETE FROM ar_deferred_lines
4367                 WHERE  customer_trx_id = p_entity_id;
4368                 --
4369                 DELETE FROM ra_customer_trx_lines
4370                 WHERE  customer_trx_id = p_entity_id;
4371                 --
4372                 DELETE FROM ra_cust_trx_line_gl_dist
4373                 WHERE  customer_trx_id = p_entity_id;
4374 
4375                 --
4376                 -- bug 1404679 : to prevent ORA-1403 error when client uses AX,
4377                 -- delete from RA_CUSTOMER_TRX
4378                 -- after lines and dist table are done
4379                 --
4380                 -- DELETE FROM ra_customer_trx
4381                 -- WHERE  customer_trx_id = p_entity_id;
4382                 --
4383 
4384                 -- Call table handler instead of doing direct delete to
4385                 -- ra_customer_Trx
4386 
4387                  arp_ct_pkg.delete_p(p_entity_id);
4388 
4389                 DELETE FROM ra_batches
4390                 WHERE  batch_id = l_batch_id
4391                 AND    NOT EXISTS ( SELECT 'x'
4392                                     FROM   ra_customer_trx t
4393                                     WHERE  t.batch_id = l_batch_id ) ;
4394 
4395 
4396                 -- bug3283678 this must be done after above delete stmt.
4397                 IF SQL%ROWCOUNT = 0
4398                 THEN
4399                      UPDATE ra_batches batch
4400                      SET    batch.purged_children_flag = 'Y'
4401                      WHERE  batch.batch_id = l_batch_id ;
4402                 END IF ;
4403                 --
4404 
4405 
4406                 --
4407                 DELETE FROM ar_distributions
4408                 WHERE  source_id in ( select adjustment_id
4409                                       from   ar_adjustments
4410                                       where  customer_trx_id = p_entity_id )
4411                 AND    source_table = 'ADJ';
4412 
4413 
4414                 --
4415 
4416                 DELETE FROM ar_adjustments
4417                 WHERE  customer_trx_id = p_entity_id;
4418 
4419 
4420                 --
4421                 DELETE FROM ra_cust_trx_line_salesreps
4422                 WHERE  customer_trx_id = p_entity_id;
4423                 --
4424                 DELETE FROM ar_notes
4425                 WHERE  customer_trx_id = p_entity_id;
4426                 --
4427                 DELETE FROM ar_action_notifications action
4428                 WHERE  call_action_id IN
4429                 (
4430                      SELECT call.call_action_id
4431                      FROM   ar_call_actions call,
4432                             ar_customer_call_topics topics
4433                      WHERE  topics.customer_trx_id = p_entity_id
4434                      AND    topics.customer_call_topic_id =
4435                                 call.customer_call_topic_id
4436                 ) ;
4437                 --
4438                 DELETE FROM ar_call_actions call
4439                 WHERE  customer_call_topic_id IN
4440                 (
4441                      SELECT topics.customer_call_topic_id
4442                      FROM   ar_customer_call_topics topics
4443                      WHERE  topics.customer_trx_id = p_entity_id
4444                 ) ;
4445                 --
4446                 DELETE FROM ar_customer_call_topics
4447                 WHERE  customer_trx_id = p_entity_id ;
4448                 --
4449                 UPDATE ar_correspondences corr
4450                 SET    corr.purged_children_flag = 'Y'
4451                 WHERE  corr.correspondence_id IN
4452                 (
4453                       SELECT sched.correspondence_id
4454                       FROM   ar_payment_schedules ps,
4455                              ar_correspondence_pay_sched sched
4456                       WHERE  ps.customer_trx_id = p_entity_id
4457                       AND    ps.payment_schedule_id =
4458                                  sched.payment_schedule_id
4459                 ) ;
4460                 --
4461                 /* bug2021662 :add RETURNING to get deleted correspondence_id
4462                 */
4463                 DELETE FROM  ar_correspondence_pay_sched sched
4464                 WHERE  payment_schedule_id IN
4465                 (
4466                       SELECT payment_schedule_id
4467                       FROM   ar_payment_schedules
4468                       WHERE  customer_trx_id = p_entity_id
4469                 )
4470                 RETURNING correspondence_id BULK COLLECT INTO del_cid ;
4471                 --
4472                 /* bug2021662 :this DELETE stmt does not work correctly
4473                 DELETE FROM  ar_correspondences corr
4474                 WHERE  corr.correspondence_id NOT IN
4475                 (
4476                       SELECT sched.correspondence_id
4477                       FROM   ar_correspondence_pay_sched sched,
4478                              ar_payment_schedules ps
4479                       WHERE  ps.customer_trx_id = p_entity_id
4480                       AND    ps.payment_schedule_id =
4481                                  sched.payment_schedule_id
4482                 ) ;
4483                 */
4484                 /* bug2021662 : instead of above stmt, created following stmt
4485        for gotton correspondence_id
4486                 */
4487     IF del_cid.count > 0 THEN
4488                    FORALL l_corr_row IN del_cid.FIRST..del_cid.LAST
4489                    DELETE FROM ar_correspondences corr
4490                    WHERE not exists
4491                    (
4492                       SELECT 'there are children records'
4493                         FROM ar_correspondence_pay_sched sched
4494                        WHERE corr.correspondence_id = sched.correspondence_id )
4495                    AND corr.correspondence_id = del_cid(l_corr_row) ;
4496     END IF;
4497                 --
4498                 DELETE FROM ar_payment_schedules
4499                 WHERE  customer_trx_id = p_entity_id;
4500 
4501                 --
4502             EXCEPTION
4503                 WHEN NO_DATA_FOUND THEN
4504                     print( p_recursive_level, ' ...No rows found while attempting to lock' );
4505                     RETURN FALSE;
4506                 WHEN locked_by_another_session THEN
4507                     print( p_recursive_level, ' ...locked by another session' );
4508                     RETURN FALSE;
4509                 WHEN deadlock_detected THEN
4510                     print( p_recursive_level, ' ...deadlock detected while deleting trxs.' );
4511                     RETURN FALSE;
4512                 WHEN OTHERS THEN
4513                     print( 1, 'Failed while deleting from the trx tables');
4514                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4515                     RAISE ;
4516             END;
4517             --
4518             -- Recursively deal with applications
4519             --
4520             DECLARE
4521                 CURSOR app_to_invoice( cp_applied_invoice_id NUMBER ) IS
4522                        SELECT  DECODE( application_type,
4523                                          'CASH',cash_receipt_id,
4524                                          'CM'  ,DECODE( applied_customer_trx_id,
4525                                                         cp_applied_invoice_id,
4526                                                         customer_trx_id ,
4527                                                         applied_customer_trx_id ) ),
4528 
4529                                applied_customer_trx_id,
4530                                application_type,
4531                                -- bug1199027
4532                                -- bug4060025 added code for CM app ex gain/loss
4533                                DECODE( application_type,
4534                                         'CASH', acctd_amount_applied_to,
4535                                         'CM', acctd_amount_applied_from - acctd_amount_applied_to ),
4536                                NVL(acctd_earned_discount_taken,0) +
4537                                    NVL(acctd_unearned_discount_taken,0)
4538                        FROM    ar_receivable_applications
4539                        WHERE
4540                        (
4541                            applied_customer_trx_id = cp_applied_invoice_id    OR
4542                            customer_trx_id         = cp_applied_invoice_id
4543                        )
4544                        FOR UPDATE OF receivable_application_id NOWAIT ;
4545 
4546                 -- bug 1715258
4547                 --
4548                 -- Select all invoice related with unpurgeable receipt
4549                 -- to add unpurgeable trx list.
4550                 --
4551                 CURSOR app_to_invoice_receipt( cp_cash_receipt_id NUMBER ) IS
4552                        SELECT applied_customer_trx_id
4553                        FROM   ar_receivable_applications
4554                        WHERE  cash_receipt_id = cp_cash_receipt_id
4555                        AND    status = 'APP';
4556 
4557                 l_application_id           NUMBER; -- receipt_id or trx_id
4558                 l_applied_customer_trx_id  NUMBER;
4559                 l_application_type         ar_receivable_applications.application_type%TYPE;
4560                 l_receipt_amount           NUMBER;
4561                 l_discount_amount          NUMBER;
4562             BEGIN
4563                 OPEN app_to_invoice( p_entity_id );
4564                 --
4565                 DELETE FROM ar_distributions
4566                 WHERE  source_id in ( SELECT receivable_application_id
4567                                       FROM   ar_receivable_applications
4568                                       WHERE
4569                                       (   applied_customer_trx_id = p_entity_id OR
4570                                           customer_trx_id = p_entity_id
4571                                       )
4572                                     )
4573                 AND    source_table = 'RA';
4574 
4575 
4576 
4577                 --
4578                 DELETE FROM ar_receivable_applications
4579                 WHERE
4580                 (
4581                     applied_customer_trx_id = p_entity_id    OR
4582                     customer_trx_id         = p_entity_id
4583                 );
4584 
4585                 --
4586                 LOOP
4587                     FETCH app_to_invoice
4588                     INTO  l_application_id,
4589                           l_applied_customer_trx_id,
4590                           l_application_type,
4591                           l_receipt_amount,
4592                           l_discount_amount ;
4593                     EXIT WHEN app_to_invoice%NOTFOUND;
4594                     --
4595                     -- This check is made so that it doesn't attempt
4596                     -- to delete again and again within this loop
4597                     --
4598                     IF l_application_type = 'CASH'
4599                     THEN
4600                         ---
4601                         p_running_total := p_running_total - l_receipt_amount
4602                                                 - l_discount_amount ;
4603                         ---
4604                         IF NOT recursive_purge( l_application_id,
4605                                                 'CR',
4606                                                 p_as_of_gl_date,
4607                                                 p_customer_id,
4608                                                 p_archive_level,
4609                                                 p_recursive_level+1,
4610                                                 p_running_total )
4611                         THEN
4612                             CLOSE app_to_invoice;
4613 
4614                             -- bug 1715258
4615                             add_to_unpurgeable_receipts( l_application_id );
4616 
4617                             -- bug 1715258
4618                             --
4619                             -- Add transaction related with unpurgeable receipt
4620                             -- to unpurgeable trx list
4621                             --
4622                             FOR r_app_to_invoice_receipt IN app_to_invoice_receipt(l_application_id )
4623                             LOOP
4624                               IF NOT in_unpurgeable_txn_list( r_app_to_invoice_receipt.applied_customer_trx_id )
4625                               THEN
4626                                 -- bug3975105 added 'N'
4627                                 print( p_recursive_level, '  Add id:' || r_app_to_invoice_receipt.applied_customer_trx_id || ' to unpurgeable transaction list', 'N');
4628                                 add_to_unpurgeable_txns(r_app_to_invoice_receipt.applied_customer_trx_id );
4629                               END IF;
4630 
4631                             END LOOP;
4632 
4633                             RETURN FALSE;
4634                         END IF;
4635                     ELSE
4636                         -- Bug4060025 Need to calc exchange gain/loss for CM
4637                         ---
4638                         p_running_total := p_running_total + l_receipt_amount ;
4639                         ---
4640                         IF NOT recursive_purge( l_application_id,
4641                                                 'CT',
4642                                                 p_as_of_gl_date,
4643                                                 p_customer_id,
4644                                                 p_archive_level,
4645                                                 p_recursive_level+1,
4646                                                 p_running_total )
4647                         THEN
4648                             CLOSE app_to_invoice;
4649                             add_to_unpurgeable_txns( l_applied_customer_trx_id );
4650                             RETURN FALSE;
4651                         END IF;
4652                     END IF;
4653                 END LOOP;
4654                 CLOSE app_to_invoice;
4655             EXCEPTION
4656                 WHEN locked_by_another_session THEN
4657                     print( p_recursive_level, ' ...locked by another session' );
4658                     RETURN FALSE; -- assume already processed in this thread
4659                 WHEN deadlock_detected THEN
4660                     print( p_recursive_level, ' ...deadlock detected in app_to_inv' );
4661                     RETURN FALSE;
4662                 WHEN OTHERS THEN
4663                     print(0,'Failed while dealing with Trx.') ;
4664                     print(0,'Error ' || SQLCODE || ' ' || SQLERRM ) ;
4665                     RAISE ;
4666             END;
4667             RETURN TRUE;
4668             -- finished 'CT' case
4669         ELSIF p_entity_type = 'CR'
4670         THEN
4671             --
4672             -- lock the receipt
4673             --
4674             Declare--Add for bug 13582725
4675                 temp_status AR_CASH_RECEIPT_HISTORY.STATUS%TYPE;
4676             BEGIN
4677              select STATUS into   temp_status
4678              FROM AR_CASH_RECEIPT_HISTORY
4679              WHERE CURRENT_RECORD_FLAG='Y' AND
4680                    CASH_RECEIPT_ID=p_entity_id;
4681             IF temp_status = 'REVERSED' THEN
4682                 print(p_recursive_level,'Its a reversed receipt. Will be taken care seperatly');
4683                 return TRUE;
4684             END IF;
4685             END;
4686 
4687             -- bug 1715258
4688             IF in_unpurgeable_receipt_list( p_entity_id )
4689             THEN
4690                 -- bug3975105 added 'S'
4691                 print( p_recursive_level, '  ...already in unpurgeable receipt list', 'S');
4692                 RETURN FALSE;
4693             END IF;
4694 
4695             DECLARE
4696                 l_record_found  VARCHAR2(10) := 'Not Found' ;
4697 
4698                 /* bug1999155: Divided select stmt which lock all transactions
4699                   records into the following stmts */
4700                 cursor dist_crh_cur is
4701                     select  'Found'  record_found
4702                     FROM    ar_distributions        dist,
4703                             ar_cash_receipt_history crh
4704                     where   crh.cash_receipt_history_id = dist.source_id (+)
4705                     AND     crh.cash_receipt_id         = p_entity_id
4706                     FOR     UPDATE OF crh.cash_receipt_id,
4707                                       dist.source_id NOWAIT;
4708 
4709                 cursor ps_cur is
4710                     select  'Found'  record_found
4711                     FROM    ar_payment_schedules ps
4712                     where   ps.cash_receipt_id  = p_entity_id
4713                     FOR     UPDATE OF ps.cash_receipt_id  NOWAIT;
4714 
4715                 cursor ra_cur is
4716                     select  'Found'  record_found
4717                     FROM    ar_receivable_applications ra
4718                     where   ra.cash_receipt_id  = p_entity_id
4719                     FOR     UPDATE OF ra.cash_receipt_id  NOWAIT;
4720 
4721                 cursor cr_cur is
4722                     select  'Found'  record_found
4723                     FROM    ar_cash_receipts  cr
4724                     where   cr.cash_receipt_id  = p_entity_id
4725                     FOR     UPDATE OF cr.cash_receipt_id  NOWAIT;
4726 
4727             BEGIN
4728                 -- lock all the transaction records
4729                 /* bug1999155: Divided the following select stmt into
4730                   some stmts. This cursor for loop is not used .
4731                 FOR lock_rec IN (
4732                                   SELECT 'Found'  record_found
4733                                   FROM   ar_distributions dist,
4734                                          ar_payment_schedules ps,
4735                                          ar_receivable_applications ra,
4736                                          ar_cash_receipt_history crh,
4737                                          ar_cash_receipts cr
4738                                   WHERE  cr.cash_receipt_id = p_entity_id
4739                                   AND    cr.cash_receipt_id = crh.cash_receipt_id
4740                                   AND    cr.cash_receipt_id = ra.cash_receipt_id (+)
4741                                   AND    crh.cash_receipt_history_id = dist.source_id (+)
4742                                   AND    cr.cash_receipt_id = ps.cash_receipt_id (+)
4743                                   FOR    UPDATE OF cr.cash_receipt_id,
4744                                                    crh.cash_receipt_id,
4745                                                    ra.cash_receipt_id,
4746                                                    dist.source_id,
4747                                                    ps.cash_receipt_id NOWAIT
4748                                )
4749                 LOOP
4750                     l_record_found := lock_rec.record_found ;
4751                 END LOOP ;
4752                 bug1999155 end */
4753 
4754                 /* bug1999155 : Open created cursors to lock */
4755                 open    dist_crh_cur;
4756 
4757                 fetch   dist_crh_cur
4758                 into l_record_found;
4759 
4760                 --
4761                 -- Need to verify if NO_DATA_FOUND will be raised if
4762                 -- the cursor does not return any row.
4763                 --
4764                 IF l_record_found = 'Not Found'
4765                 THEN
4766                    RETURN TRUE ; -- No Data Found
4767                 END IF ;
4768 
4769                 close   dist_crh_cur;
4770 
4771                 open ps_cur;
4772                 close ps_cur;
4773 
4774                 open ra_cur;
4775                 close ra_cur;
4776 
4777                 open cr_cur;
4778                 close cr_cur;
4779 
4780             EXCEPTION
4781                 -- This receipt has already been deleted by an earlier process
4782                 -- Ideal case when 2 invoices I1 and I2 have the same receipt R1
4783                 -- applied against it.
4784                 WHEN NO_DATA_FOUND THEN
4785                     RETURN TRUE; -- assume already processed in this thread
4786                 WHEN locked_by_another_session THEN
4787                     print( p_recursive_level, ' ...locked by another session' );
4788                     RETURN FALSE; -- assume already processed in this thread
4789                 WHEN OTHERS THEN
4790                     print( p_recursive_level, ' ...Failed while trying to lock CR' );
4791                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4792                     RAISE;
4793             END;
4794             --
4795             --  Check if it paid by the same customer
4796             --
4797             DECLARE
4798                 l_same_customer  VARCHAR2(1);
4799             BEGIN
4800                 IF p_customer_id IS NOT NULL THEN
4801                     BEGIN
4802                         SELECT  'Y'
4803                         INTO    l_same_customer
4804                         FROM    ar_cash_receipts
4805                         WHERE   cash_receipt_id = p_entity_id
4806                         AND     NVL( pay_from_customer, p_customer_id ) = p_customer_id ;
4807                     EXCEPTION
4808                         WHEN NO_DATA_FOUND THEN
4809                             print( p_recursive_level, ' ...Pymt made by different customer' );
4810                             RETURN FALSE ;
4811                         WHEN OTHERS THEN
4812                             print( p_recursive_level, ' ...Oracle Error at Cust Id. Check' );
4813                             RAISE;
4814                     END ;
4815                 --
4816                 END IF ;
4817             END;
4818             --
4819             -- check if open/closed
4820             --
4821             DECLARE
4822                 l_ps_status    VARCHAR2(2);
4823             BEGIN
4824                 SELECT  status
4825                 INTO    l_ps_status
4826                 FROM    ar_payment_schedules
4827                 WHERE   cash_receipt_id = p_entity_id
4828                 FOR     UPDATE OF payment_schedule_id NOWAIT ;
4829 
4830                 IF l_ps_status = 'OP'  THEN
4831                     print( p_recursive_level,'  ...still open' );
4832                     RETURN FALSE;
4833                 END IF;
4834 
4835             EXCEPTION
4836                 WHEN locked_by_another_session THEN
4837                     print( p_recursive_level, ' ...pymt_sch locked by another session' );
4838                     RETURN ( FALSE ) ;
4839 
4840             END;
4841             -- search for unpurgeable history records
4842             DECLARE
4843                 l_unpurgeable_histories   NUMBER;
4844             BEGIN
4845                 SELECT  COUNT(*)
4846                 INTO    l_unpurgeable_histories
4847                 FROM    ar_cash_receipt_history
4848                 WHERE   cash_receipt_id = p_entity_id
4849                 AND
4850                 (
4851                     posting_control_id = -3          OR
4852                     gl_date > p_as_of_gl_date
4853                 );
4854                 --
4855                 IF l_unpurgeable_histories >0  THEN
4856                     print( p_recursive_level, '  ...unpurgeable CRH exist' );
4857                     RETURN FALSE;
4858                 END IF;
4859                 -- 5715943
4860                 SELECT COUNT(*)
4861                 INTO   l_unpurgeable_histories
4862                 FROM   ar_cash_receipt_history
4863                 WHERE  cash_receipt_id = p_entity_id
4864                 AND    current_record_flag = 'Y'
4865                 AND
4866                 (
4867                      ( status =  'CLEARED' AND factor_flag = 'Y' ) OR
4868                      ( status IN ( 'APPROVED', 'REMITTED', 'CONFIRMED', 'REVERSED' ) )
4869                 ) ;
4870                 --
4871                 -- 5715943
4872                 IF l_unpurgeable_histories > 0 THEN
4873                     print( p_recursive_level, '  ...which has unpurgeable histories'||'_'||p_entity_id );
4874                     RETURN FALSE;
4875                 END IF;
4876             END;
4877             --
4878             -- check if there are any applications
4879             --
4880 
4881             DECLARE
4882                 l_unpurgeable_applications     NUMBER;
4883             BEGIN
4884                 SELECT  COUNT(*)
4885                 INTO    l_unpurgeable_applications
4886                 FROM    ar_receivable_applications
4887                 WHERE   cash_receipt_id = p_entity_id
4888                 AND
4889                 (
4890                     posting_control_id = -3       OR
4891                     gl_date            > p_as_of_gl_date
4892                 );
4893 
4894                 IF  l_unpurgeable_applications > 0
4895                 THEN
4896                     print( p_recursive_level, '  ...unpurgeable applications' );
4897                     RETURN FALSE;
4898                 END IF;
4899             END;
4900             -- bug3655859 Added following check
4901             --
4902             -- check if there are related bank statement in CE
4903             --
4904 
4905             DECLARE
4906                 l_statement_reconciliation     NUMBER;
4907             BEGIN
4908                 SELECT  COUNT(*)
4909                 INTO    l_statement_reconciliation
4910                 FROM    ar_cash_receipt_history crh,
4911                         ce_statement_reconciliations sr
4912                 WHERE   cash_receipt_id = p_entity_id
4913                 AND     crh.cash_receipt_history_id = sr.reference_id
4914                 AND     sr.reference_type = 'RECEIPT'
4915                 AND     sr.current_record_flag = 'Y'
4916                 AND     sr.status_flag = 'M' ;
4917 
4918                 IF  l_statement_reconciliation > 0
4919                 THEN
4920                     print( p_recursive_level, '  ...bank statement exists in CE ' );
4921                     RETURN FALSE;
4922                 END IF;
4923             END;
4924             --
4925             -- delete records
4926             --
4927             DECLARE
4928     -- bug3384792 added
4929     TYPE BatchTyp IS TABLE OF NUMBER(15) INDEX BY BINARY_INTEGER;
4930                 l_batch_id  BatchTyp ;
4931                 l_batch_id_null  BatchTyp ;
4932                 l_trans_id NUMBER(15) ;
4933 
4934                 --
4935                 -- lock ar_batches row before deleting
4936                 --
4937     -- bug33843792 removed outer join and changed to cursor
4938     CURSOR cur_batch_id(l_receipt_id NUMBER) IS
4939                 SELECT bat.batch_id
4940                 FROM   ar_batches bat,
4941                        (SELECT distinct batch_id
4942       FROM ar_cash_receipt_history
4943                   WHERE  cash_receipt_id = l_receipt_id) crh
4944                  WHERE   crh.batch_id = bat.batch_id
4945                 FOR    UPDATE OF bat.batch_id NOWAIT ;
4946     --
4947     CURSOR cur_trans_id(l_receipt_id NUMBER) IS
4948                 SELECT bat.transmission_request_id
4949                 FROM   ar_batches bat,
4950                        ar_cash_receipt_history crh
4951                 WHERE  crh.cash_receipt_id = l_receipt_id
4952                 AND    crh.batch_id = bat.batch_id
4953     AND    crh.first_posted_record_flag = 'Y';
4954 
4955             BEGIN
4956                 -- bug3384792 get batch info
4957     OPEN cur_batch_id(p_entity_id) ;
4958     FETCH cur_batch_id BULK COLLECT INTO l_batch_id ;
4959     CLOSE cur_batch_id ;
4960                 --
4961     OPEN cur_trans_id(p_entity_id) ;
4962     FETCH cur_trans_id INTO l_trans_id ;
4963     CLOSE cur_trans_id ;
4964                 --
4965                 -- bug3975105 added 'N'
4966                 print( p_recursive_level, '  ...deleting rows', 'N');
4967                 --
4968                 -- Call entity handler to delete from ar_cash_Receipts.
4969                 -- DELETE FROM ar_cash_receipts
4970                 -- WHERE  cash_receipt_id = p_entity_id;
4971                 ARP_CASH_RECEIPTS_PKG.DELETE_P(p_entity_id);
4972 
4973                 --
4974                 DELETE FROM ar_distributions
4975                 WHERE  source_id in
4976                 (
4977                   SELECT cash_receipt_history_id
4978                   FROM   ar_cash_receipt_history
4979                   WHERE  cash_receipt_id = p_entity_id
4980                 )
4981                 AND    source_table = 'CRH';
4982 
4983                                 --
4984                 -- Bug 2021718: call the entity handler for
4985                 -- ar_cash_receipt_history rather
4986                 -- then doing the delete in this package.
4987                 -- DELETE FROM ar_cash_receipt_history
4988                 -- WHERE  cash_receipt_id = p_entity_id;
4989 
4990                 arp_cr_history_pkg.delete_p_cr(p_entity_id);
4991 
4992                 --
4993     -- bug3384792 there could be multiple records for one receipt.
4994     -- To handle the case, use BULK for delete stmt for ar_batches.
4995     -- And for performance, check whether or not there is batch.
4996     IF l_batch_id.COUNT>0
4997     THEN
4998        FORALL i IN l_batch_id.FIRST..l_batch_id.LAST
4999                    DELETE FROM ar_batches
5000                    WHERE  batch_id = l_batch_id(i)
5001                    AND    NOT EXISTS ( SELECT 'x'
5002                                     FROM   ar_cash_receipt_history h
5003                                     WHERE  h.batch_id = l_batch_id(i) );
5004 
5005                    --
5006                    -- There could be multiple records within this batch
5007                    -- In this case, the above statement would not delete
5008                    -- this record.
5009                    --
5010        FOR j IN l_batch_id.FIRST..l_batch_id.LAST
5011        LOOP
5012           IF SQL%BULK_ROWCOUNT(j) = 0
5013           THEN
5014                          UPDATE ar_batches
5015                          SET purged_children_flag = 'Y'
5016                          WHERE batch_id = l_batch_id(j);
5017           END IF;
5018        END LOOP;
5019 
5020 
5021                    --
5022        --
5023        IF l_trans_id IS NOT NULL
5024        THEN
5025           DELETE from ar_transmissions trans
5026           WHERE  transmission_request_id = l_trans_id
5027           AND    NOT EXISTS
5028           (
5029               SELECT '*'
5030              FROM ar_batches batch
5031              WHERE batch.transmission_request_id = l_trans_id
5032           );
5033        END IF;
5034     END IF;
5035 
5036                 --
5037                 DELETE FROM ar_payment_schedules
5038                 WHERE  cash_receipt_id = p_entity_id;
5039 
5040                 --
5041 
5042                 DELETE FROM ar_rate_adjustments
5043                 WHERE  cash_receipt_id = p_entity_id;
5044 
5045 
5046                 --
5047             EXCEPTION
5048                 WHEN NO_DATA_FOUND THEN
5049                     print( p_recursive_level, ' ...No rows found while attempting to lock' );
5050                     RETURN FALSE;
5051                 WHEN locked_by_another_session THEN
5052                     print( p_recursive_level, ' ...locked by another session' );
5053                     RETURN FALSE;
5054                 WHEN deadlock_detected THEN
5055                     print( p_recursive_level, ' ...deadlock detected while deleting from appls.' );
5056                     RETURN FALSE;
5057                 WHEN OTHERS THEN
5058                     print( 1, 'Failed while deleting from CR tables');
5059                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5060                     RAISE ;
5061             END;
5062             --
5063             -- deal with applications
5064             --
5065             DECLARE
5066                 CURSOR app_from_receipt( cp_cash_receipt_id NUMBER ) IS
5067                        SELECT  applied_customer_trx_id,
5068                                -- bug1199027
5069                                acctd_amount_applied_to,
5070                                NVL(acctd_earned_discount_taken,0) +
5071                                    NVL(acctd_unearned_discount_taken,0),
5072                                NVL(acctd_amount_applied_from,0) -
5073                                    NVL(acctd_amount_applied_to,0),
5074                                gl_date
5075                        FROM    ar_receivable_applications
5076                        WHERE   cash_receipt_id = cp_cash_receipt_id
5077                        AND     status          = 'APP'
5078                        FOR     UPDATE OF receivable_application_id NOWAIT ;
5079 
5080                 l_applied_customer_trx_id  NUMBER;
5081                 l_receipt_amount           NUMBER;
5082                 l_discount_amount          NUMBER;
5083                 l_gain_loss                NUMBER;
5084                 l_gl_date                  DATE;
5085                 l_period_name              VARCHAR2(15) ;
5086                 l_status                   BOOLEAN;
5087                 l_cnt_unapp_rows           NUMBER;
5088 
5089 
5090             BEGIN
5091                 OPEN app_from_receipt( p_entity_id );
5092                 ---
5093                 ---
5094                 LOOP
5095                     FETCH app_from_receipt
5096                     INTO  l_applied_customer_trx_id,
5097                           l_receipt_amount ,
5098                           l_discount_amount,
5099                           l_gain_loss,
5100                           l_gl_date ;
5101                     EXIT  WHEN app_from_receipt%NOTFOUND;
5102                     --
5103                     p_running_total := p_running_total - l_receipt_amount
5104                                            - l_discount_amount ;
5105 
5106                     -- To update ar_archive_control_detail with the
5107                     -- cash receipt amount. This rec. appln. record
5108                     -- will not exist when archive procedure is
5109                     -- called recursively.
5110 
5111                     l_period_name := get_period_name ( l_gl_date );
5112 /* bug1199027
5113                     l_status := ins_control_detail_table ( NVL(l_receipt_amount,0),
5114                                                           'CASH',
5115                                                           'Y',
5116                                                           l_period_name,
5117                                                           l_archive_id  ) ;
5118 
5119                     IF (l_discount_amount <> 0)
5120                     THEN
5121                         l_status := ins_control_detail_table ( l_discount_amount,
5122                                                               'DISC',
5123                                                               'Y',
5124                                                               l_period_name,
5125                                                               l_archive_id  ) ;
5126                     END IF ;
5127 
5128                     IF (l_gain_loss <> 0)
5129                     THEN
5130                         l_status := ins_control_detail_table ( l_gain_loss,
5131                                                               'EXCH',
5132                                                               'Y',
5133                                                               l_period_name,
5134                                                               l_archive_id  ) ;
5135                     END IF ;
5136 */
5137 
5138                     --
5139                     DELETE FROM ar_receivable_applications
5140                     WHERE  cash_receipt_id = p_entity_id;
5141 
5142 
5143                     --
5144                     IF NOT recursive_purge( l_applied_customer_trx_id,
5145                                             'CT',
5146                                             p_as_of_gl_date,
5147                                             p_customer_id,
5148                                             p_archive_level,
5149                                             p_recursive_level+1,
5150                                             p_running_total )
5151                     THEN
5152                         CLOSE app_from_receipt;
5153                         add_to_unpurgeable_txns( l_applied_customer_trx_id );
5154                         RETURN FALSE;
5155                     END IF;
5156                 END LOOP;
5157                 CLOSE app_from_receipt;
5158                 --
5159                 DELETE FROM ar_distributions
5160                 WHERE  source_id in ( SELECT receivable_application_id
5161                                       FROM   ar_receivable_applications
5162                                       WHERE  cash_receipt_id = p_entity_id
5163                                       AND    status  <> 'APP' )
5164 
5165                 AND    source_table = 'RA' ;
5166 
5167 
5168 
5169                --
5170 
5171                 --
5172                 --  Need to lock the rows for status <> 'APP'.
5173                 --  This delete is necessary to delete all the UNAPP rows
5174                 --  in case of a single receipt applied against a single
5175                 --  invoice.
5176                 --
5177                 BEGIN
5178                     FOR I in ( SELECT receivable_application_id
5179                                FROM   ar_receivable_applications
5180                                WHERE  cash_receipt_id = p_entity_id
5181                                AND    status <> 'APP'
5182                                FOR  UPDATE OF receivable_application_id NOWAIT )
5183                     LOOP
5184                         DELETE FROM ar_receivable_applications
5185                         WHERE  receivable_application_id =
5186                                    I.receivable_application_id;
5187 
5188                 /*---------------------------------+
5189                  | Calling central MRC library     |
5190                  | for MRC Integration             |
5191                  +---------------------------------*/
5192 
5193               /*  ar_mrc_engine.maintain_mrc_data(
5194                         p_event_mode        => 'DELETE',
5195                         p_table_name        => 'AR_RECEIVABLE_APPLICATIONS',
5196                         p_mode              => 'SINGLE',
5197                         p_key_value         => I.receivable_application_id);*/
5198 
5199                         --
5200                     END LOOP ;
5201                 EXCEPTION
5202                     WHEN locked_by_another_session THEN
5203                          print( p_recursive_level, ' ...appl.locked by another session' );
5204                          RETURN FALSE;
5205                     WHEN deadlock_detected THEN
5206                          print( p_recursive_level, ' ...deadlock detected while deleting UNAPP rows
5207 ' );
5208                          RETURN FALSE;
5209                 END ;
5210                 --
5211             EXCEPTION
5212                 WHEN locked_by_another_session THEN
5213                     print( p_recursive_level, ' ...locked by another session' );
5214                     RETURN FALSE;
5215                 WHEN deadlock_detected THEN
5216                     print( p_recursive_level, ' ...deadlock detected in app_from_receipt' );
5217                     RETURN FALSE;
5218                 WHEN OTHERS THEN
5219                     print( p_recursive_level, ' ...Failed while trying to lock rec. app.');
5220                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5221                     RAISE ;
5222             END;
5223             RETURN TRUE;
5224         END IF;
5225         RETURN TRUE; -- Not reqd.
5226 
5227     EXCEPTION
5228         WHEN OTHERS THEN
5229             print( 1, 'Failed in Recursive purge') ;
5230             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5231             RAISE ;
5232     END;
5233     --
5234 
5235    --Add for bug 13582725
5236    PROCEDURE arch_purge_rev_receipts( p_as_of_gl_date  IN  DATE,
5237                                       r_archive_level  IN  VARCHAR2,
5238                                       p_archive_id     IN  NUMBER,
5239                                       p_total_worker   IN  NUMBER,
5240                                       p_worker_number  IN  NUMBER,
5241                                       p_customer_id    IN  NUMBER
5242                                     ) IS
5243    cursor c_receipt( cp_customer_id   NUMBER,
5244                    cp_total_worker    NUMBER,
5245                    cp_worker_number   NUMBER,
5246                    cp_as_of_gl_date   DATE,
5247                    cp_max_recpt_id    NUMBER
5248                   ) IS
5249   select CR.CASH_RECEIPT_ID
5250   FROM AR_CASH_RECEIPTS CR,
5251        AR_CASH_RECEIPT_HISTORY CRH
5252   WHERE
5253        CR.CASH_RECEIPT_ID=CRH.CASH_RECEIPT_ID AND
5254        CRH.STATUS ='REVERSED' AND
5255        CRH.CURRENT_RECORD_FLAG='Y' AND
5256        MOD(NVL(CR.PAY_FROM_CUSTOMER,0), cp_total_worker) + 1 = cp_worker_number AND
5257        NVL(cp_customer_id, 0 ) = DECODE(cp_customer_id,NULL,0,CR.PAY_FROM_CUSTOMER) AND
5258        CRH.GL_POSTED_DATE <=cp_as_of_gl_date AND
5259        CRH.POSTING_CONTROL_ID <> -3 AND
5260        CR.CASH_RECEIPT_ID > cp_max_recpt_id AND
5261        not exists (select 'x' from ar_receivable_applications RA
5262                    where RA.CASH_RECEIPT_ID=CR.CASH_RECEIPT_ID AND
5263                          RA.GL_POSTED_DATE > cp_as_of_gl_date AND
5264                          RA.POSTING_CONTROL_ID <> -3 )
5265        ORDER BY CR.CASH_RECEIPT_ID ;
5266 
5267   TYPE rec_table IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
5268   l_rec_table  rec_table;
5269   l_rec_cnt        BINARY_INTEGER := 0;
5270   l_rec_rows       BINARY_INTEGER := 0;
5271   l_max_record     NUMBER;
5272   l_max_rcpt_id    NUMBER := 0;
5273   l_rcpt_id        AR_CASH_RECEIPTS.cash_receipt_id%TYPE;
5274   l_existence      NUMBER;
5275   r_archive_id     NUMBER;
5276   r_arch_status    BOOLEAN;
5277   ra_total_count   NUMBER;
5278   ra_posted_count  NUMBER;
5279 
5280   -- Commented as a fix to bug - 13653152
5281   /*r_rec_app_key_value_list   gl_ca_utility_pkg.r_key_value_arr;
5282     r_ar_dist_key_value_list   gl_ca_utility_pkg.r_key_value_arr;
5283     r_rate_adj_key_value_list  gl_ca_utility_pkg.r_key_value_arr;
5284     r_ar_ps_key_value_list     gl_ca_utility_pkg.r_key_value_arr;*/
5285 
5286    BEGIN
5287        l_max_record :=500;
5288        r_archive_id :=p_archive_id;
5289        LOOP
5290             l_rec_cnt :=0;
5291             open c_receipt(p_customer_id,p_total_worker,p_worker_number,p_as_of_gl_date,l_max_rcpt_id);
5292             FETCH c_receipt BULK COLLECT INTO l_rec_table LIMIT  l_max_record;
5293             CLOSE c_receipt;
5294             l_rec_cnt := l_rec_table.COUNT;
5295             IF l_rec_cnt > 0 THEN
5296                  l_max_rcpt_id := l_rec_table(l_rec_table.LAST);
5297                  FOR l_rec_rows in l_rec_table.FIRST..l_rec_table.LAST LOOP
5298                  SAVEPOINT prior_to_recpt;
5299                  BEGIN
5300                       l_rcpt_id :=l_rec_table(l_rec_rows);
5301                       l_rec_table.DELETE(l_rec_rows);
5302                       print(0,'Cash_receipt_id:'||l_rcpt_id||' p_worker_number:'||p_worker_number);
5303                       select count(*) into ra_total_count
5304                       from ar_receivable_applications
5305                       where CASH_RECEIPT_ID=l_rcpt_id;
5306 
5307                       select count(*) into ra_posted_count
5308                       from ar_receivable_applications
5309                       where CASH_RECEIPT_ID=l_rcpt_id AND
5310                       gl_posted_date  <= p_as_of_gl_date;
5311 
5312                       IF ra_total_count <> ra_posted_count THEN
5313                            print(0,'...All records in RA are not posted for this Reversed Receipt');
5314                            GOTO continue_rcpt;
5315                       ELSE
5316                            r_arch_status := archive_rev_receipt( l_rcpt_id,
5317                                                                  r_archive_id,
5318                                                                  r_archive_level) ;
5319                           IF r_arch_status = FALSE THEN
5320                                   print( 0,'Archive Failed for Receipt:'||l_rcpt_id) ;
5321                                   rollback to prior_to_recpt;
5322                                   GOTO continue_rcpt;
5323                           ELSE
5324                                   print( 0,'Archived Successfully, Now Purging records') ;
5325                                   DECLARE
5326                                    CURSOR c_cr ( cr_id NUMBER ) IS
5327                                         SELECT 'X' FROM  AR_CASH_RECEIPTS
5328                                         WHERE CASH_RECEIPT_ID=cr_id
5329                                         FOR UPDATE OF CASH_RECEIPT_ID NOWAIT;
5330 
5331                                    CURSOR c_crh (cr_id NUMBER) IS
5332                                         SELECT 'X' FROM  AR_CASH_RECEIPT_HISTORY
5333                                         WHERE CASH_RECEIPT_ID=cr_id
5334                                         FOR UPDATE OF CASH_RECEIPT_ID NOWAIT;
5335 
5336                                    CURSOR c_ard( cr_id number) IS
5337                                        SELECT 'X' FROM ar_distributions
5338                                        WHERE  source_id in
5339                                        (
5340                                           SELECT cash_receipt_history_id
5341                                           FROM   ar_cash_receipt_history
5342                                           WHERE  cash_receipt_id = cr_id
5343                                         )
5344                                        AND    source_table = 'CRH'
5345                                        FOR UPDATE OF SOURCE_ID NOWAIT;
5346 
5347                                     CURSOR c_ra( cr_id number) IS
5348                                          SELECT 'X' FROM ar_receivable_applications
5349                                          WHERE  cash_receipt_id = cr_id
5350                                          FOR UPDATE OF cash_receipt_id NOWAIT;
5351                                     CURSOR c_ap( cr_id number) IS
5352                                          SELECT 'X' FROM ar_payment_schedules
5353                                          WHERE  cash_receipt_id = cr_id
5354                                          FOR UPDATE OF cash_receipt_id NOWAIT;
5355                                     CURSOR c_ara( cr_id number) IS
5356                                          SELECT 'X' FROM ar_rate_adjustments
5357                                          WHERE  cash_receipt_id = cr_id
5358                                          FOR UPDATE OF cash_receipt_id NOWAIT;
5359                                   BEGIN
5360                                   open c_cr(l_rcpt_id);
5361                                   close c_cr;
5362                                   open c_crh(l_rcpt_id);
5363                                   close c_crh;
5364                                   open c_ard(l_rcpt_id);
5365                                   close c_ard;
5366                                   open c_ra(l_rcpt_id);
5367                                   close c_ra;
5368                                   open c_ap(l_rcpt_id);
5369                                   close c_ap;
5370                                   open c_ara(l_rcpt_id);
5371                                   close c_ara;
5372 
5373 
5374                                   DELETE FROM ar_distributions
5375                                   WHERE  source_id in
5376                                   (
5377                                     SELECT cash_receipt_history_id
5378                                     FROM   ar_cash_receipt_history
5379                                     WHERE  cash_receipt_id = l_rcpt_id
5380                                   )
5381                                   AND    source_table = 'CRH';
5382 
5383                                   /*---------------------------------+
5384                                    | Calling central MRC library     |
5385                                    | for MRC Integration             |
5386                                    +---------------------------------*/
5387           	                  -- Commented as a fix to bug - 13653152
5388                                   /*ar_mrc_engine.maintain_mrc_data(
5389                                           p_event_mode        => 'DELETE',
5390                                           p_table_name        => 'AR_DISTRIBUTIONS',
5391                                           p_mode              => 'BATCH',
5392                                           p_key_value_list    => r_ar_dist_key_value_list);*/
5393 
5394                                   arp_cr_history_pkg.delete_p_cr(l_rcpt_id);
5395 
5396                                   ARP_CASH_RECEIPTS_PKG.DELETE_P(l_rcpt_id);
5397 
5398                                   DELETE FROM ar_receivable_applications
5399                                   WHERE  cash_receipt_id = l_rcpt_id;
5400 
5401                                  /*---------------------------------+
5402                                   | Calling central MRC library     |
5403                                   | for MRC Integration             |
5404                                   +---------------------------------*/
5405 			        -- Commented as a fix to bug - 13653152
5406                                 /*ar_mrc_engine.maintain_mrc_data(
5407                                     p_event_mode        => 'DELETE',
5408                                     p_table_name        => 'AR_RECEIVABLE_APPLICATIONS',
5409                                     p_mode              => 'BATCH',
5410                                     p_key_value_list    => r_rec_app_key_value_list);*/
5411 
5412 
5413                                 DELETE FROM ar_payment_schedules
5414                                 WHERE  cash_receipt_id = l_rcpt_id;
5415 
5416                                 /*---------------------------------+
5417                                  | Calling central MRC library     |
5418                                  | for MRC Integration             |
5419                                  +---------------------------------*/
5420 		                -- Commented as a fix to bug - 13653152
5421                                 /*ar_mrc_engine.maintain_mrc_data(
5422                                         p_event_mode        => 'DELETE',
5423                                         p_table_name        => 'AR_PAYMENT_SCHEDULES',
5424                                         p_mode              => 'BATCH',
5425                                         p_key_value_list    => r_ar_ps_key_value_list);*/
5426 
5427                                 DELETE FROM ar_rate_adjustments
5428                                 WHERE  cash_receipt_id = l_rcpt_id;
5429 
5430                                 /*---------------------------------+
5431                                  | Calling central MRC library     |
5432                                  | for MRC Integration             |
5433                                  +---------------------------------*/
5434 		                -- Commented as a fix to bug - 13653152
5435                                 /*ar_mrc_engine.maintain_mrc_data(
5436                                         p_event_mode        => 'DELETE',
5437                                         p_table_name        => 'AR_RATE_ADJUSTMENTS',
5438                                         p_mode              => 'BATCH',
5439                                         p_key_value_list    => r_rate_adj_key_value_list);*/
5440 
5441                                  print(0,'Purged Successfully');
5442                                  END;
5443                                  commit;
5444 
5445                           END IF ;
5446                       END IF;
5447                       <<continue_rcpt>>
5448                       print(0,' Picking another Receipt','N');
5449                       print( 0, '------------------------------------------------------------', 'N' );
5450                  EXCEPTION
5451                       WHEN locked_by_another_session THEN
5452                       print( 0,'...locked by another session ') ;
5453                       print( 0,'------------------------------------------------------------');
5454                       ROLLBACK TO prior_to_recpt;
5455                       WHEN savepoint_not_established THEN
5456                       print( 0,'...Savepoint not established') ;
5457                       print( 0,'------------------------------------------------------------');
5458                       ROLLBACK ;
5459                       RAISE ;
5460                       WHEN deadlock_detected THEN
5461                       print(0,'...Deadlock Detected');
5462                       print( 0,'------------------------------------------------------------');
5463                       WHEN OTHERS THEN
5464                       print( 1, 'Failed in the for loop') ;
5465                       print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5466                       ROLLBACK TO prior_to_recpt;
5467                       RAISE ;
5468 
5469                  END;
5470                  END LOOP;
5471             END IF;
5472        EXIT WHEN l_rec_cnt < l_max_record;
5473        END LOOP;
5474 
5475    EXCEPTION
5476         WHEN OTHERS THEN
5477             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5478             print( 1, 'Failed in arch_purge_rev_receipts') ;
5479             ROLLBACK ;
5480             RAISE;
5481    END arch_purge_rev_receipts;
5482 
5483     PROCEDURE drive_by_invoice( errbuf           OUT NOCOPY VARCHAR2,
5484                                 retcode          OUT NOCOPY NUMBER,
5485                                 p_start_gl_date  IN  DATE, --bug1199027
5486                                 p_end_gl_date    IN  DATE, --bug1199027
5487                                 p_as_of_gl_date  IN  DATE, --bug1199027
5488                                 p_archive_level  IN  VARCHAR2,
5489                                 p_archive_id     IN  NUMBER,
5490                                 p_total_worker   IN  NUMBER,
5491                                 p_worker_number  IN  NUMBER,
5492                                 p_customer_id    IN  NUMBER,
5493                                 p_short_flag     IN  VARCHAR2) IS
5494         --
5495         --  Earlier, it was driven from RA_CUST_TRX_LINE_GL_DIST
5496         --  To improve the performance, the code is changed
5497         --  so that it drives from AR_PAYMENT_SCHEDULES.
5498         --  This will not handle the cases where the
5499         --  open_receivable flag for the transaction_type is set
5500         --  to 'N'. This is the intended behaviour to improve
5501         --  the performance.
5502         --
5503         -- bug1199027 Use cp_start/end_gl_date instead of l_as_of_gl_date
5504         CURSOR c_inv( cp_start_gl_date DATE, cp_end_gl_date DATE,
5505                       cp_customer_id   NUMBER ,
5506                       cp_max_trx_id    NUMBER) IS
5507         SELECT ct.customer_trx_id          customer_trx_id
5508         FROM   ra_cust_trx_types           ctt,
5509                ra_customer_trx             ct,
5510                ar_payment_schedules        ps
5511         WHERE  ct.initial_customer_trx_id  IS NULL
5512         AND    ps.customer_trx_id          = ct.customer_trx_id
5513         -- bug1199027
5514         AND    ps.gl_date_closed           BETWEEN cp_start_gl_date
5515                                            AND     cp_end_gl_date
5516         -- bug2967315 added DM
5517         AND    ps.class                    IN ('INV','CM', 'DM')
5518         AND    NVL(cp_customer_id, 0 )     = DECODE(cp_customer_id, NULL,0,
5519                                                  ct.bill_to_customer_id )
5520         AND    ps.terms_sequence_number     = 1
5521         AND    ctt.cust_trx_type_id        = ct.cust_trx_type_id
5522         AND    ctt.type                    NOT IN ('DEP', 'GUAR' )
5523         -- bug2472294
5524         -- AND    ctt.post_to_gl              = 'Y'  -- just handle gl_date < cut-off date
5525         AND    ct.complete_flag = 'Y'
5526         AND    ct.customer_trx_id > cp_max_trx_id  -- bug1715258
5527         ORDER BY ct.customer_trx_id  ;  -- bug1715258
5528 
5529         -- bug1715258
5530         r_inv  c_inv%ROWTYPE ;
5531         l_max_trx_id     NUMBER := 0 ;
5532         l_max_record     NUMBER := 500 ;
5533 
5534         TYPE inv_table IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
5535         l_inv_table      inv_table;
5536         -- bug3990664 added
5537         l_inv_table_null inv_table;
5538         l_inv_rows       BINARY_INTEGER := 0;
5539         l_inv_cnt        BINARY_INTEGER := 0;
5540         l_trx_id         NUMBER ;
5541         -- bug1715258
5542 
5543 
5544         l_running_total  NUMBER ;
5545         l_existence      NUMBER(2) ;
5546         -- l_archive_status BOOLEAN ; --bug1199027
5547         l_arch_status    BOOLEAN ; -- bug1199027
5548         --l_as_of_gl_date  DATE ; -- bug1199027
5549         l_cnt_of_chains  NUMBER := 0 ;
5550         l_org_id         NUMBER ; /* Bug 5290308 */
5551 
5552     BEGIN
5553 
5554   /*Bug 5349016 Commenting the below code as it is handled in ARARCALL.sql
5555         -- Bug 5290308 : Set the org_context
5556         fnd_profile.get('ORG_ID', l_org_id);
5557         mo_global.init ('AR');
5558         mo_global.set_policy_context('S',l_org_id);
5559         arp_global.init_global(l_org_id);
5560         arp_standard.init_standard(l_org_id);
5561   */
5562 
5563         /* bug3975105 added */
5564   IF p_short_flag = 'Y' THEN
5565            l_short_flag := p_short_flag;
5566      print(0,'(Show only unpurged items)');
5567   END IF;
5568         --
5569         --l_as_of_gl_date := TRUNC(to_date(p_as_of_gl_date,'DD-MON-YYYY'));
5570         -- bug1199027
5571         --l_as_of_gl_date := FND_DATE.canonical_to_date(p_as_of_gl_date) ;
5572         --
5573         l_archive_id := p_archive_id ;
5574         --
5575         print( 0,'Starting Archive and Purge Process');
5576         print( 0,'----------------------------------');
5577         print(0,'Archiving Reversed Receipts'); --Add for bug 13582725
5578 
5579         arch_purge_rev_receipts(p_as_of_gl_date,
5580                                 p_archive_level,
5581                                 p_archive_id   ,
5582                                 p_total_worker ,
5583                                 p_worker_number,
5584                                 p_customer_id
5585                                );
5586 
5587         print(0,'Done with Archiving Reversed Receipts');
5588         print(0,'Archiving Invoices');
5589         --
5590 
5591         -- bug 1715258
5592         -- Change logic to prevent "Snapshot too old" error
5593         --
5594         LOOP
5595 
5596            l_inv_cnt := 0 ;
5597 
5598            /* 3990664: added initialization */
5599            l_inv_table := l_inv_table_null ;
5600 
5601            -- bug1199027 Use cp_start/end_gl_date instead of l_as_of_gl_date
5602            OPEN c_inv(p_start_gl_date,p_end_gl_date,
5603         p_customer_id , l_max_trx_id) ;
5604 
5605            -- bug3990664: changed to BULK FETCH
5606               FETCH c_inv BULK COLLECT INTO l_inv_table LIMIT l_max_record;
5607 
5608            CLOSE c_inv ;
5609 
5610            -- bug1715258
5611            -- set max trx id to l_max_trx_id in order not to process
5612            -- same trx id.
5613            -- bug3990664 : added
5614            l_inv_cnt := l_inv_table.COUNT ;
5615 
5616            -- bug3990664 : modified
5617            /* Bug fix 5290308 : Try to access the table only if it contains records */
5618            IF l_inv_cnt  > 0 THEN
5619                l_max_trx_id := l_inv_table(l_inv_table.last) ;
5620            END IF;
5621 
5622            IF l_inv_cnt > 0 THEN
5623               FOR l_inv_rows IN l_inv_table.first..l_inv_table.last LOOP
5624 
5625               BEGIN
5626                 --
5627                 SAVEPOINT prior_to_inv;
5628                 --
5629                 l_running_total := 0 ;
5630                 l_cnt_of_chains := l_cnt_of_chains + 1 ;
5631                 l_trx_id        := l_inv_table(l_inv_rows); -- bug1715258
5632                 l_inv_table.delete(l_inv_rows); -- bug1715258
5633                 --
5634                 -- Just to make sure that this trx is not deleted
5635                 -- by another instance when called recursively
5636                 --
5637                 SELECT 1
5638                 INTO   l_existence
5639                 FROM   RA_CUSTOMER_TRX
5640                 WHERE  customer_trx_id = l_trx_id
5641                 FOR    UPDATE OF customer_trx_id  NOWAIT ;
5642 
5643                 -- lock all the corresponding records
5644 
5645                 IF l_existence = 0 THEN
5646                    print(0, l_trx_id || ' ...already purged by another instance') ;
5647                    GOTO continue ;
5648                 END IF ;
5649     --
5650                 IF recursive_purge( l_trx_id,
5651                                     'CT',
5652                                     p_as_of_gl_date,
5653                                     p_customer_id,
5654                                     p_archive_level,
5655                                     0,
5656                                     l_running_total )
5657                 THEN
5658                     IF l_running_total = 0
5659                     THEN
5660                        -- bug1199027
5661                        l_arch_status := upd_arch_control_detail( p_archive_id ) ;
5662                        l_control_detail_array.delete ;
5663                        --
5664                        -- bug3975105 added 'S'
5665                        print( 0,'Successful purge' , 'S');
5666                        COMMIT;
5667                        --
5668                     ELSE
5669                        print( 1,'...Running total is not Zero ');
5670                        -- bug3975105 added 'N'
5671                        print( 0, 'Rollback work', 'N');
5672                        add_to_unpurgeable_txns( l_trx_id );
5673                        -- bug1199027
5674                        l_control_detail_array.delete ;
5675                        --
5676                        ROLLBACK TO prior_to_inv;
5677                     END IF ;
5678                 ELSE
5679                     -- bug3975105 added 'N'
5680                     print( 0, 'Rollback Work', 'N');
5681                     add_to_unpurgeable_txns( l_trx_id );
5682                     -- bug1199027
5683                     l_control_detail_array.delete ;
5684                     --
5685                     ROLLBACK TO prior_to_inv;
5686                 END IF;
5687                 << continue >>
5688                 -- bug3975105 added 'N'
5689                 print( 0, '------------------------------------------------------------', 'N' );
5690                 IF ( l_cnt_of_chains MOD 500 ) = 0 THEN
5691                      -- bug3975105 added 'N'
5692                      print(0, 'No. of Chains processed so far : ' || l_cnt_of_chains , 'N') ;
5693                      print( 0, '------------------------------------------------------------', 'N' );
5694                 END IF ;
5695               EXCEPTION
5696                 WHEN NO_DATA_FOUND THEN
5697                    print( 0,'Id : ' || l_trx_id ) ;
5698                    print( 0, '...deleted by another instance' );
5699                    print( 0, '------------------------------------------------------------' );
5700                    ROLLBACK TO prior_to_inv; -- bug1999155
5701                    -- bug1199027
5702                    IF ( l_cnt_of_chains MOD 500 ) = 0 THEN
5703                         print(0, 'No. of Chains processed so far : ' || l_cnt_of_chains ) ;
5704                         print( 0, '------------------------------------------------------------' );
5705        END IF;
5706                 WHEN locked_by_another_session THEN
5707                    print( 0,'...locked by another session ') ;
5708                    print( 0, '------------------------------------------------------------' );
5709                    ROLLBACK TO prior_to_inv;
5710                    -- bug1199027
5711                    IF ( l_cnt_of_chains MOD 500 ) = 0 THEN
5712                         print(0, 'No. of Chains processed so far : ' || l_cnt_of_chains ) ;
5713                         print( 0, '------------------------------------------------------------' );
5714                    END IF ;
5715                 WHEN savepoint_not_established THEN
5716                    print( 0,'...Savepoint not established') ;
5717                    print( 0, '------------------------------------------------------------' );
5718                    ROLLBACK ; -- bug1999155
5719                    RAISE ;
5720                 WHEN OTHERS THEN
5721                    print( 1, 'Failed in the for loop') ;
5722                    print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5723                    ROLLBACK TO prior_to_inv; -- bug1999155
5724                    RAISE ;
5725               END ;
5726               END LOOP ;
5727 
5728            END IF;
5729 
5730            -- bug1715258
5731            --
5732            -- Exit when already get last record
5733            --
5734            EXIT WHEN l_inv_cnt < l_max_record ;
5735 
5736         END LOOP;
5737         print( 0,'------------------------------------------------------------ ' );
5738         print( 0,'Total No. of Chains Processed : ' || l_cnt_of_chains );
5739         print( 0,'End Time : ' || to_char(sysdate,'dd-mon-yyyy hh:mi:ss') );
5740         print( 0,'------------------------------ End ------------------------- ' );
5741 
5742     EXCEPTION
5743         WHEN OTHERS THEN
5744             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
5745             print( 1, 'Failed in drive_by_invoice') ;
5746             ROLLBACK ;
5747             print( 0,'------------------------------------------------------------ ' );
5748             print( 0,'Total No. of Chains Processed : ' || l_cnt_of_chains );
5749             print( 0,'End Time : ' || to_char(sysdate,'dd-mon-yyyy hh:mi:ss') );
5750             print( 0,'------------------------------ End ------------------------- ' );
5751             fnd_file.put_line (FND_FILE.LOG, 'Error ' || SQLCODE || ' ' || SQLERRM ) ;
5752             RAISE ;
5753     END;
5754 
5755 END;