DBA Data[Home] [Help]

PACKAGE BODY: APPS.AR_PURGE

Source


1 PACKAGE BODY AR_PURGE AS
2 /* $Header: ARPURGEB.pls 120.32.12010000.2 2008/11/10 09:29:05 rviriyal 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 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     --
595     -- Insert into AR_ARCHIVE_HEADER
596     --
597     FUNCTION archive_header( p_customer_trx_id IN NUMBER ,
598                              p_archive_id      IN NUMBER) RETURN BOOLEAN IS
599     BEGIN
600     DECLARE
601         CURSOR header_cursor ( cp_customer_trx_id NUMBER ) IS
602         SELECT ctt.type  type,			/* transaction_class */
603                ctt.name  name,			/* transaction_type */
604                ct.customer_trx_id  trx_id, 	/* transaction_id */
605                decode(ctt.type, 'CM', ctt_prev.type)
606                    related_trx_type,            /* related_transaction_class */
607                decode(ctt.type, 'CM', ctt_prev.name)
608                    related_trx_id,              /* related_transaction_type */
609                decode(ctt.type, 'CM', ct.previous_customer_trx_id)
610                    prev_trx_id ,                /* related_transaction_id */
611                ct.trx_number trx_number,        /* transaction_number */
612                ct.trx_date   trx_date,          /* transaction_date */
613                batch.name    batch_name,
614                bs.name       batch_source_name,
615                sob.name      sob_name,
616                ctlgd.amount  amount,
617                ctlgd.acctd_amount acctd_amount,
618                to_number('') exch_gain_loss,	      /* exchange_gain_loss */
619                to_number('') earned_disc_taken,	      /* earned_discount_taken */
620                to_number('') unearned_disc_taken,     /* unearned_discount_taken */
621                to_number('') acctd_earned_disc_taken, /* acctd_earned_discount_taken */
622                to_number('') acctd_unearned_disc_taken,	 /* acctd_unearned_discount_taken */
623                '' adj_trx_type,				/* type */
624                '' adj_type,				/* adjustment_type */
625                ctt.post_to_gl post_to_gl,
626                ctt.accounting_affect_flag open_receivable,
627                '' cash_rcpt_status,		/* cash_receipt_status */
628                '' cash_rcpt_hist_status,	/* cash_receipt_history_status */
629                lu.meaning reason_code, 		/* reason_code_meaning */
630                substrb(bill_party.party_name,1,50)  bill_to_cust_name,
631                cust_bill.account_number bill_to_cust_no,
632                su_bill.location bill_to_cust_loc,
633                bill_loc.address1 bill_to_cust_addr1,
634                bill_loc.address2 bill_to_cust_addr2,
635                bill_loc.address3 bill_to_cust_addr3,
636                bill_loc.address4 bill_to_cust_addr4,
637                bill_loc.city bill_to_cust_city,
638                bill_loc.state bill_to_cust_state,
639                bill_loc.country bill_to_cust_country,
640                bill_loc.postal_code bill_to_cust_zip,
641                substrb(ship_party.party_name,1,50) ship_to_cust_name,
642                cust_ship.account_number ship_to_cust_no,
643                su_ship.location      ship_to_cust_loc,
644                ship_loc.address1    ship_to_cust_addr1,
645                ship_loc.address2    ship_to_cust_addr2,
646                ship_loc.address3    ship_to_cust_addr3,
647                ship_loc.address4    ship_to_cust_addr4,
648                ship_loc.city        ship_to_cust_city,
649                ship_loc.state       ship_to_cust_state,
650                ship_loc.country     ship_to_cust_country,
651                ship_loc.postal_code ship_to_cust_zip,
652                remit_loc.address1   remit_to_cust_addr1,
653                remit_loc.address2   remit_to_cust_addr2,
654                remit_loc.address3   remit_to_cust_addr3,
655                remit_loc.address4   remit_to_cust_addr4,
656                remit_loc.city       remit_to_cust_city,
657                remit_loc.state      remit_to_cust_state,
658                remit_loc.country    remit_to_cust_country,
659                remit_loc.postal_code remit_to_cust_zip,
660                sales.name             salesrep_name,
661                term.name              term_name,
662                ct.term_due_date       term_due_date,
663                ct.printing_last_printed last_printed,
664                ct.printing_option printing_option,
665                ct.purchase_order purchase_order,
666                ct.comments            comments,
667                ct.exchange_rate_type exch_rate_type,
668                ct.exchange_date exch_date,
669                ct.exchange_rate exch_rate,
670                ct.invoice_currency_code curr_code,
671                nvl(ctlgd.gl_date, ct.trx_date) gl_date,
672                to_date(NULL) reversal_date,	/* reversal_date */
673                '' reversal_category,		/* reversal_category */
674                '' reversal_reason_code,		/* reversal_reason_code_meaning */
675                '' reversal_comments, 		/* reversal_comments */
676                ct.attribute_category attr_category,
677                ct.attribute1 attr1,
678                ct.attribute2 attr2,
679                ct.attribute3 attr3,
680                ct.attribute4 attr4,
681                ct.attribute5 attr5,
682                ct.attribute6 attr6,
683                ct.attribute7 attr7,
684                ct.attribute8 attr8,
685                ct.attribute9 attr9,
686                ct.attribute10 attr10,
687                ct.attribute11 attr11,
688                ct.attribute12 attr12,
689                ct.attribute13 attr13,
690                ct.attribute14 attr14,
691                ct.attribute15 attr15,
692                '' rcpt_method,             /* receipt_method_name */
693                ct.waybill_number waybill_no,
694                doc.name doc_name,
695                ct.doc_sequence_value doc_seq_value,
696                ct.start_date_commitment st_date_commitment,
697                ct.end_date_commitment en_date_commitment,
698                rule.name invoicing_rule,
699                '' bank_acct_name,
700                to_date(NULL) deposit_date,	/* deposit_date */
701                to_number('') factor_disc_amount,/* factor_discount_amount */
702                ct.interface_header_context     int_hdr_context,
703                ct.interface_header_attribute1  int_hdr_attr1,
704                ct.interface_header_attribute2  int_hdr_attr2,
705                ct.interface_header_attribute3  int_hdr_attr3,
706                ct.interface_header_attribute4  int_hdr_attr4,
707                ct.interface_header_attribute5  int_hdr_attr5,
708                ct.interface_header_attribute6  int_hdr_attr6,
709                ct.interface_header_attribute7  int_hdr_attr7,
710                ct.interface_header_attribute8  int_hdr_attr8,
711                ct.interface_header_attribute9  int_hdr_attr9,
712                ct.interface_header_attribute10 int_hdr_attr10,
713                ct.interface_header_attribute11 int_hdr_attr11,
714                ct.interface_header_attribute12 int_hdr_attr12,
715                ct.interface_header_attribute13 int_hdr_attr13,
716                ct.interface_header_attribute14 int_hdr_attr14,
717                ct.interface_header_attribute15 int_hdr_attr15,
718                '' bank_deposit_no,           /* bank_deposit_number */
719                '' reference_type,            /* reference_type */
720                to_number('') reference_id,   /* reference_id */
721                '' cust_rcpt_reference,	     /* customer_receipt_reference */
722                '' bank_acct_name2 /* bank_account_name */
723         FROM   ar_lookups        lu,
724                ra_rules          rule,
725                ra_cust_trx_types ctt_prev,
726                ra_cust_trx_types ctt,
727                ra_batch_sources  bs,
728                ra_batches        batch,
729                fnd_document_sequences doc,
730                gl_sets_of_books  sob,
731                hz_cust_accounts  cust_bill,
732                hz_parties        bill_party,
733                hz_cust_site_uses su_bill,
734                hz_cust_acct_sites addr_bill,
735                hz_party_sites     bill_ps,
736                hz_locations       bill_loc,
737                hz_cust_accounts  cust_ship,
738                hz_parties        ship_party,
739                hz_cust_site_uses su_ship,
740                hz_cust_acct_sites addr_ship,
741                hz_party_sites     ship_ps,
742                hz_locations       ship_loc,
743                hz_cust_acct_sites addr_remit,
744                hz_party_sites     remit_ps,
745                hz_locations       remit_loc,
746                iby_trxn_extensions_v iby,
747                ra_salesreps      sales,
748                ra_terms          term,
749                ra_cust_trx_line_gl_dist ctlgd,
750                ra_customer_trx   ct_prev,
751                ra_customer_trx   ct
752         WHERE  lu.lookup_code (+) = ct.reason_code
753         AND    lu.lookup_type (+) = 'INVOICING_REASON'
754         AND    iby.trxn_extension_id(+)     = ct.payment_trxn_extension_id
755         AND    rule.rule_id (+)             = ct.invoicing_rule_id
756         AND    ctt.cust_trx_type_id         = ct.cust_trx_type_id
757         AND    bs.batch_source_id           = ct.batch_source_id
758         AND    batch.batch_id (+)           = ct.batch_id
759         AND    doc.doc_sequence_id (+)      = ct.doc_sequence_id
760         AND    sob.set_of_books_id          = ct.set_of_books_id
761         AND    cust_bill.cust_account_id (+) = ct.bill_to_customer_id
762         AND    cust_bill.party_id           = bill_party.party_id(+)
763         AND    su_bill.site_use_id (+)      = ct.bill_to_site_use_id
764         AND    addr_bill.cust_acct_site_id (+) = su_bill.cust_acct_site_id
765         AND    addr_bill.party_site_id      = bill_ps.party_site_id(+)
766         AND    bill_loc.location_id(+)      = bill_ps.location_id
767         AND    cust_ship.cust_account_id(+) = ct.ship_to_customer_id
768         AND    cust_ship.party_id           = ship_party.party_id(+)
769         AND    su_ship.site_use_id (+)      = ct.ship_to_site_use_id
770         AND    addr_ship.cust_acct_site_id (+) = su_ship.cust_acct_site_id
771         AND    addr_ship.party_site_id      = ship_ps.party_site_id(+)
772         AND    ship_loc.location_id (+)        = ship_ps.location_id
773         AND    addr_remit.cust_acct_site_id (+) = ct.remit_to_address_id
774         AND    addr_remit.party_site_id     = remit_ps.party_site_id(+)
775         AND    remit_loc.location_id(+)        = remit_ps.location_id
776         AND    sales.salesrep_id(+)         = ct.primary_salesrep_id
777         AND    term.term_id (+)             = ct.term_id
778         AND    ctlgd.customer_trx_id        = ct.customer_trx_id
779         AND    ctlgd.account_class          = 'REC'
780         AND    ctlgd.latest_rec_flag        = 'Y'
781         AND    ct.previous_customer_trx_id  = ct_prev.customer_trx_id(+)
782         AND    ct_prev.cust_trx_type_id     = ctt_prev.cust_trx_type_id(+)
783         AND    ct.customer_trx_id           = cp_customer_trx_id
784         UNION
785         --------------------------------------------------------------------
786         -- ADJ: adjustments
787         --------------------------------------------------------------------
788         SELECT 'ADJ'  type,			  /* transaction_class */
789                ''     name,                       /* transaction_type */
790                adj.adjustment_id  trx_id,         /* transaction_id */
791                ctt.type  related_trx_type,	  /* related_transaction_class */
792                ctt.name  related_trx_id,	  /* related_transaction_type */
793                ct.customer_trx_id prev_trx_id,    /* related_transaction_id */
794                adj.adjustment_number trx_number,  /* transaction_number */
795                adj.apply_date trx_date,		  /* transaction_date */
796                ''  batch_name,  		  /* batch_name */
797                ''  batch_source_name, 		  /* batch_source_name */
798                sob.name  sob_name,
799                adj.amount amount,
800                adj.acctd_amount acctd_amount,
801                to_number('') exch_gain_loss,	        /* exchange_gain_loss */
802                to_number('') earned_disc_taken,		/* earned_discount_taken */
803                to_number('') unearned_disc_taken,	/* unearned_discount_taken */
804                to_number('') acctd_earned_disc_taken,   /* acctd_earned_discount_taken */
805                to_number('') acctd_unearned_disc_taken,	/* acctd_unearned_discount_taken */
806                adj.type  adj_trx_type,
807                adj.adjustment_type adj_type,
808                '' post_to_gl,		        /* post_to_gl */
809                '' open_receivable,		/* accounting_affect_flag */
810                '' cash_rcpt_status,	        /* cash_receipt_status */
811                '' cash_rcpt_hist_status,	/* cash_receipt_history_status */
812                lu.meaning reason_code,    	/* reason_code_meaning */
813                substrb(cust_party.party_name,1,50)  bill_to_cust_name,	/* bill_to_customer_name */
814                cust.account_number bill_to_cust_no,	/* bill_to_customer_number */
815                '' bill_to_cust_loc,		/* bill_to_customer_location */
816                '' bill_to_cust_addr1,		/* bill_to_customer_address1 */
817                '' bill_to_cust_addr2,		/* bill_to_customer_address2 */
818                '' bill_to_cust_addr3,		/* bill_to_customer_address3 */
819                '' bill_to_cust_addr4,		/* bill_to_customer_address4 */
820                '' bill_to_cust_city,		/* bill_to_customer_city */
821                '' bill_to_cust_state,		/* bill_to_customer_state */
822                '' bill_to_cust_country,		/* bill_to_customer_country */
823                '' bill_to_cust_zip,		/* bill_to_customer_postal_code */
824                '' ship_to_cust_name,		/* ship_to_customer_name */
825                '' ship_to_cust_no,		/* ship_to_customer_number */
826                '' ship_to_cust_loc,		/* ship_to_customer_location */
827                '' ship_to_cust_addr1,           /* ship_to_customer_address1 */
828                '' ship_to_cust_addr2,           /* ship_to_customer_address2 */
829                '' ship_to_cust_addr3,		/* ship_to_customer_address3 */
830                '' ship_to_cust_addr4,		/* ship_to_customer_address4 */
831                '' ship_to_cust_city,		/* ship_to_customer_city */
832                '' ship_to_cust_state,           /* ship_to_customer_state */
833                '' ship_to_cust_country,         /* ship_to_customer_country */
834                '' ship_to_cust_zip,		/* ship_to_customer_postal_code */
835                '' remit_to_cust_addr1,		/* remit_to_customer_address1 */
836                '' remit_to_cust_addr2,          /* remit_to_customer_address2 */
837                '' remit_to_cust_addr3,          /* remit_to_customer_address3 */
838                '' remit_to_cust_addr4,          /* remit_to_customer_address4 */
839                '' remit_to_cust_city,           /* remit_to_customer_city */
840                '' remit_to_cust_state,          /* remit_to_customer_state */
841                '' remit_to_cust_country,        /* remit_to_customer_country */
842                '' remit_to_cust_zip,	        /* remit_to_customer_postal_code */
843                '' salesrep_name,		/* salesrep_name */
844                '' term_name, 		        /* term_name */
845                to_date(NULL) term_due_date,       /* term_due_date */
846                to_date(NULL) last_printed,        /* printing_last_printed */
847                '' printing_option,	        /* printing_option */
848                '' purchase_order, 		/* purchase_order */
849                '' comments,   		        /* comments */
850                '' exch_rate_type,		/* exchange_rate_type */
851                to_date(NULL) exch_date, 	/* exchange_rate_date */
852                to_number('') exch_rate, 	/* exchange_rate */
853                ct.invoice_currency_code curr_code,
854                nvl(adj.gl_date, ct.trx_date)  gl_date,
855                to_date(NULL) reversal_date,		/* reversal_date */
856                '' reversal_catergory,			/* reversal_category */
857                '' reversal_reason_code,			/* reversal_reason_code_meaning */
858                '' reversal_comments, 			/* reversal_comments */
859                adj.attribute_category attr_catergory,
860                adj.attribute1 attr1,
861                adj.attribute2 attr2,
862                adj.attribute3 attr3,
863                adj.attribute4 attr4,
864                adj.attribute5 attr5,
865                adj.attribute6 attr6,
866                adj.attribute7 attr7,
867                adj.attribute8 attr8,
868                adj.attribute9 attr9,
869                adj.attribute10 attr10,
870                adj.attribute11 attr11,
871                adj.attribute12 attr12,
872                adj.attribute13 attr13,
873                adj.attribute14 attr14,
874                adj.attribute15 attr15,
875                '' rcpt_method,		 /* receipt_method_name */
876                '' waybill_no,			/* waybill_number */
877                doc.name doc_name,
878                adj.doc_sequence_value doc_seq_value,
879                to_date(NULL) st_date_commitment,		/* start_date_commitment */
880                to_date(NULL) en_date_commitment,		/* end_date_commitment */
881                '' invoicing_rule,			/* invoicing_rule_name */
882                '' bank_acct_name,			/* bank_account_name */
883                to_date(NULL) deposit_date,		/* deposit_date */
884                to_number('') factor_disc_amount,/* factor_discount_amount */
885                '' int_hdr_context,		/* interface_header_context */
886                '' int_hdr_attr1,		/* interface_header_attribute1 */
887                '' int_hdr_attr2,		/* interface_header_attribute2 */
888                '' int_hdr_attr3,		/* interface_header_attribute3 */
889                '' int_hdr_attr4,		/* interface_header_attribute4 */
890                '' int_hdr_attr5,		/* interface_header_attribute5 */
891                '' int_hdr_attr6,		/* interface_header_attribute6 */
892                '' int_hdr_attr7,		/* interface_header_attribute7 */
893                '' int_hdr_attr8,		/* interface_header_attribute8 */
894                '' int_hdr_attr9,		/* interface_header_attribute9 */
895                '' int_hdr_attr10,		/* interface_header_attribute10 */
896                '' int_hdr_attr11,		/* interface_header_attribute11 */
897                '' int_hdr_attr12,		/* interface_header_attribute12 */
898                '' int_hdr_attr13,		/* interface_header_attribute13 */
899                '' int_hdr_attr14,		/* interface_header_attribute14 */
900                '' int_hdr_attr15,		/* interface_header_attribute15 */
901                '' bank_deposit_no,		/* bank_deposit_number */
902                '' reference_type,		/* reference_type */
903                to_number('') reference_id,	/* reference_id */
904                '' cust_rcpt_reference,		/* customer_receipt_reference */
905                '' bank_acct_name2               /* bank_account_name */
906         FROM   ra_cust_trx_types ctt,
907                fnd_document_sequences doc,
908                gl_sets_of_books  sob,
909                ar_lookups        lu,
910                ar_adjustments    adj,
911                hz_cust_accounts  cust,
912                hz_parties        cust_party,
913                ra_customer_trx   ct
914         WHERE  lu.lookup_code (+)      = adj.reason_code
915         AND    lu.lookup_type (+)      = 'ADJUST_REASON'
916         AND    ctt.cust_trx_type_id    = ct.cust_trx_type_id
917         AND    doc.doc_sequence_id (+) = adj.doc_sequence_id
918         AND    sob.set_of_books_id     = adj.set_of_books_id
919         AND    adj.customer_trx_id     = ct.customer_trx_id
920                /* do not archive unaccrued adjustments */
921         AND    adj.status <> 'U'
922         AND    cust.cust_account_id (+)    = ct.bill_to_customer_id
923         AND    cust.party_id = cust_party.party_id (+)
924         AND    ct.customer_trx_id      = cp_customer_trx_id
925         UNION
926         --------------------------------------------------------------------
927         -- REC: cash receipts
928         --------------------------------------------------------------------
929         SELECT cr.type type,			/* transaction_class */
930                '' name,			        /* transaction_type */
931                cr.cash_receipt_id trx_id, 	/* transaction_id */
932                '' related_trx_type,		/* related_transaction_class */
933                '' related_trx_id,		/* related_transaction_type */
934                to_number('') prev_trx_id, 	/* related_transaction_id */
935                cr.receipt_number trx_number,	/* transaction_number */
936                cr.receipt_date trx_date,	/* transaction_date */
937                batch.name batch_name,
938                bs.name    batch_source_name,
939                sob.name   sob_name,
940                cr.amount  amount,
941                -- bug1199027
942                sum( ra.acctd_amount_applied_to ) acctd_amount,/* acctd_amount */
943                sum( ra.acctd_amount_applied_from - ra.acctd_amount_applied_to )
944                         exch_gain_loss, /* exchange_gain_loss */
945                sum( ra.earned_discount_taken ) earned_disc_taken ,
946                sum( ra.unearned_discount_taken ) unearned_disc_taken ,
947                sum( ra.acctd_earned_discount_taken ) acctd_earned_disc_taken ,
948                sum( ra.acctd_unearned_discount_taken ) acctd_unearned_disc_taken ,
949                cr.type adj_trx_type,
950                '' adj_type,			/* adjustment_type */
951                ''  post_to_gl,                  /* post_to_gl */
952                ''  open_receivable,             /* accounting_affect_flag */
953                cr.status cash_rcpt_status,	/* cash_receipt_status */
954                crh.status cash_rcpt_hist_status,/* cash_receipt_history_status */
955                '' reason_code, 				        /* reason_code_meaning */
956                substrb(cust_party.party_name,1,50)  bill_to_cust_name,		/* bill_to_customer_name */
957                cust.account_number bill_to_cust_no,	        /* bill_to_customer_number */
958                su.location bill_to_cust_loc,			/* bill_to_customer_location */
959                substrb(loc.address1, 1, 80) bill_to_cust_addr1, /* bill_to_customer_address1 */
960                substrb(loc.address2, 1, 80) bill_to_cust_addr2, /* bill_to_customer_address2 */
961                substrb(loc.address3, 1, 80) bill_to_cust_addr3, /* bill_to_customer_address3 */
962                substrb(loc.address4, 1, 80) bill_to_cust_addr4, /* bill_to_customer_address4 */
963                loc.city  bill_to_cust_city,			/* bill_to_customer_city */
964                loc.state bill_to_cust_state,			/* bill_to_customer_state */
965                loc.country bill_to_cust_country,               /* bill_to_customer_country */
966                loc.postal_code bill_to_cust_zip,		/* bill_to_postal_code*/
967                '' ship_to_cust_name,		/* ship_to_customer_name */
968                '' ship_to_cust_no, 		/* ship_to_customer_number */
969                '' ship_to_cust_loc, 		/* ship_to_customer_location */
970                '' ship_to_cust_addr1, 		/* ship_to_customer_address1 */
971                '' ship_to_cust_addr2, 		/* ship_to_customer_address2 */
972                '' ship_to_cust_addr3,		/* ship_to_customer_address3 */
973                '' ship_to_cust_addr4, 		/* ship_to_customer_address4 */
974                '' ship_to_cust_city, 		/* ship_to_customer_city */
975                '' ship_to_cust_state, 		/* ship_to_customer_state */
976                '' ship_to_cust_country, 	/* ship_to_customer_country */
977                '' ship_to_cust_zip,		/* ship_to_customer_postal_code */
978                '' remit_to_cust_addr1,  	/* remit_to_customer_address1 */
979                '' remit_to_cust_addr2,		/* remit_to_customer_address2 */
980                '' remit_to_cust_addr3,		/* remit_to_customer_address3 */
981                '' remit_to_cust_addr4,		/* remit_to_customer_address4 */
982                '' remit_to_cust_city, 		/* remit_to_customer_city */
983                '' remit_to_cust_state, 		/* remit_to_customer_state */
984                '' remit_to_cust_country, 	/* remit_to_customer_country */
985                '' remit_to_cust_zip, 		/* remit_to_customer_postal_code */
986                '' salesrep_name, 		/* salesrep_name */
987                '' term_name, 			/* term_name */
988                to_date(NULL) term_due_date,	/* term_due_date */
989                to_date(NULL) last_printed,	/* printing_last_printed */
990                '' printing_option,			/* printing_option */
991                '' purchase_order,  		/* purchase_order */
992                cr.comments comments,
993                cr.exchange_rate_type exch_rate_type,
994                cr.exchange_date exch_date,
995                cr.exchange_rate exch_rate,
996                cr.currency_code curr_code,
997                nvl(crh.gl_date, cr.receipt_date) gl_date,
998                cr.reversal_date reversal_date,
999                substrb(lu1.meaning, 1, 20) reversal_category, 	/* reversal_category */
1000                lu2.meaning reversal_reason_code,       		/* reversal_reason_code_meaning */
1001                cr.reversal_comments reversal_comments,
1002                substrb(cr.attribute_category, 1, 30) attr_category,
1003                cr.attribute1 attr1,
1004                cr.attribute2 attr2,
1005                cr.attribute3 attr3,
1006                cr.attribute4 attr4,
1007                cr.attribute5 attr5,
1008                cr.attribute6 attr6,
1009                cr.attribute7 attr7,
1010                cr.attribute8 attr8,
1011                cr.attribute9 attr9,
1012                cr.attribute10 attr10,
1013                cr.attribute11 attr11,
1014                cr.attribute12 attr12,
1015                cr.attribute13 attr13,
1016                cr.attribute14 attr14,
1017                cr.attribute15 attr15,
1018                rm.name rcpt_method,		/* receipt_method_name */
1019                '' waybill_no,			/* waybill_number */
1020                doc.name doc_name,
1021                cr.doc_sequence_value doc_seq_value,
1022                to_date(NULL) st_date_commitment,		/* start_date_commitment */
1023                to_date(NULL) en_date_commitment,		/* end_date_commitment */
1024                '' invoicing_rule,       /* invoicing_rule_name */
1025                '' bank_acct_name,
1026                cr.deposit_date deposit_date,
1027                cr.factor_discount_amount factor_disc_amount,
1028                '' int_hdr_context,      /* interface_header_context */
1029                '' int_hdr_attr1,        /* interface_header_attribute1 */
1030                '' int_hdr_attr2,	/* interface_header_attribute2 */
1031                '' int_hdr_attr3,	/* interface_header_attribute3 */
1032                '' int_hdr_attr4,	/* interface_header_attribute4 */
1033                '' int_hdr_attr5,	/* interface_header_attribute5 */
1034                '' int_hdr_attr6,	/* interface_header_attribute6 */
1035                '' int_hdr_attr7,	/* interface_header_attribute7 */
1036                '' int_hdr_attr8,	/* interface_header_attribute8 */
1037                '' int_hdr_attr9,	/* interface_header_attribute9 */
1038                '' int_hdr_attr10,	/* interface_header_attribute10 */
1039                '' int_hdr_attr11,	/* interface_header_attribute11 */
1040                '' int_hdr_attr12,	/* interface_header_attribute12 */
1041                '' int_hdr_attr13,	/* interface_header_attribute13 */
1042                '' int_hdr_attr14,	/* interface_header_attribute14 */
1043                '' int_hdr_attr15, 	/* interface_header_attribute15 */
1044                batch_remit.bank_deposit_number bank_deposit_no,
1045                cr.reference_type reference_type,
1046                cr.reference_id reference_id,
1047                cr.customer_receipt_reference cust_rcpt_reference,
1048                cba.bank_account_name bank_acct_name2
1049         FROM   ar_lookups lu1,
1050                ar_lookups lu2,
1051                ar_receipt_methods rm,
1052                ar_batch_sources  bs,
1053                ar_batches        batch,
1054                ar_batches        batch_remit,
1055                ce_bank_accounts  cba,
1056                ce_bank_acct_uses ba2,
1057                ce_bank_branches_v bb,
1058                fnd_document_sequences doc,
1059                gl_sets_of_books  sob,
1060                hz_cust_acct_sites addr,
1061                hz_party_sites     party_site,
1062                hz_locations       loc,
1063                hz_cust_site_uses su,
1064                hz_cust_accounts  cust,
1065                hz_parties        cust_party,
1066                iby_trxn_extensions_v iby,
1067                ar_receivable_applications ra,
1068                ar_receivable_applications ra1, --bug1199027
1069                ar_cash_receipt_history crh,
1070                ar_cash_receipt_history crh_batch,
1071                ar_cash_receipt_history crh_remit,
1072                ar_cash_receipts  cr
1073         WHERE  lu1.lookup_code (+)  = cr.reversal_category
1074         AND    lu1.lookup_type (+)  = 'REVERSAL_CATEGORY_TYPE'
1075         AND    lu2.lookup_code (+)  = cr.reversal_reason_code
1076         AND    lu2.lookup_type (+)  = 'CKAJST_REASON'
1077         AND    iby.trxn_extension_id(+)     = cr.payment_trxn_extension_id
1078         AND    ba2.bank_account_id          = cba.bank_account_id (+)
1079         AND    ba2.bank_acct_use_id (+)     = cr.remit_bank_acct_use_id
1080         AND    bb.branch_party_id  (+)      = cba.bank_branch_id
1081         AND    rm.receipt_method_id (+)     = cr.receipt_method_id
1082         AND    cust.cust_account_id (+)     = cr.pay_from_customer
1083         AND    cust.party_id                = cust_party.party_id(+)
1084         AND    su.site_use_id (+)           = cr.customer_site_use_id
1085         AND    addr.cust_acct_site_id (+)   = su.cust_acct_site_id
1086         AND    addr.party_site_id           = party_site.party_site_id(+)
1087         AND    loc.location_id (+)          = party_site.location_id
1088         AND    doc.doc_sequence_id (+)      = cr.doc_sequence_id
1089         AND    sob.set_of_books_id          = cr.set_of_books_id
1090                /* get CR batch info */
1091         AND    bs.batch_source_id (+)       = batch.batch_source_id
1092         AND    batch.batch_id (+)           = crh_batch.batch_id
1093         AND    crh_batch.first_posted_record_flag = 'Y'
1094         AND    crh_batch.cash_receipt_id    = cr.cash_receipt_id
1095                /* get current crh record for gl_date */
1096         AND    crh.cash_receipt_id          = cr.cash_receipt_id
1097         AND    crh.current_record_flag      = 'Y'
1098                /* get remittance batch */
1099         AND    crh_remit.batch_id           = batch_remit.batch_id(+)
1100         AND    nvl(crh_remit.cash_receipt_history_id, -99) in
1101                    ( SELECT nvl( min(crh1.cash_receipt_history_id), -99 )
1102                      from   ar_cash_receipt_history crh1
1103                      where  crh1.cash_receipt_id  = cr.cash_receipt_id
1104                      and    crh1.status = 'REMITTED' )
1105         AND    crh_remit.status (+)         = 'REMITTED'
1106         AND    crh_remit.cash_receipt_id(+) = cr.cash_receipt_id
1107         AND    cr.cash_receipt_id           = ra.cash_receipt_id
1108         -- bug1199027
1109         and    ra.cash_receipt_id           = ra1.cash_receipt_id
1110         and    ra.status = ra1.status
1111         and    ra1.applied_customer_trx_id  = cp_customer_trx_id
1112         and    ra1.status = 'APP'
1113         -- bug2859402 Don't insert duplicate cash record.
1114         and    not exists (
1115                   select 'already purged'
1116                     from ar_archive_header aah
1117                    where aah.transaction_id = cr.cash_receipt_id
1118                      and aah.transaction_class = 'CASH' )
1119         GROUP BY cr.type,			/* transaction_class */
1120                  cr.cash_receipt_id, 		/* transaction_id */
1121                  cr.receipt_number,		/* transaction_number */
1122                  cr.receipt_date,		/* transaction_date */
1123                  batch.name,
1124                  bs.name,
1125                  sob.name,
1126                  cr.amount,
1127                  cr.type,
1128                  cr.status,			/* cash_receipt_status */
1129                  crh.status,			/* cash_receipt_history_status */
1130                  cust_party.party_name,		/* bill_to_customer_name */
1131                  cust.account_number,		/* bill_to_customer_number */
1132                  su.location,			/* bill_to_customer_location */
1133                  substrb(loc.address1, 1, 80), 	/* bill_to_customer_address1 */
1134                  substrb(loc.address2, 1, 80),	/* bill_to_customer_address2 */
1135                  substrb(loc.address3, 1, 80), 	/* bill_to_customer_address3 */
1136                  substrb(loc.address4, 1, 80), 	/* bill_to_customer_address4 */
1137                  loc.city,			/* bill_to_customer_city */
1138                  loc.state,			/* bill_to_customer_state */
1139                  loc.country,			/* bill_to_customer_country */
1140                  loc.postal_code,		/* bill_to_customer_postal_code */
1141                  cr.comments,
1142                  cr.exchange_rate_type,
1143                  cr.exchange_date,
1144                  cr.exchange_rate,
1145                  cr.currency_code,
1146                  nvl(crh.gl_date, cr.receipt_date),
1147                  cr.reversal_date,
1148                  substrb(lu1.meaning, 1, 20), 	/* reversal_category */
1149                  lu2.meaning,       		/* reversal_reason_code_meaning */
1150                  cr.reversal_comments,
1151                  substrb(cr.attribute_category, 1, 30),
1152                  cr.attribute1,
1153                  cr.attribute2,
1154                  cr.attribute3,
1155                  cr.attribute4,
1156                  cr.attribute5,
1157                  cr.attribute6,
1158                  cr.attribute7,
1159                  cr.attribute8,
1160                  cr.attribute9,
1161                  cr.attribute10,
1162                  cr.attribute11,
1163                  cr.attribute12,
1164                  cr.attribute13,
1165                  cr.attribute14,
1166                  cr.attribute15,
1167                  rm.name,			/* receipt_method_name */
1168                  doc.name,
1169                  cr.doc_sequence_value,
1170                  cr.deposit_date,
1171                  cr.factor_discount_amount,
1172                  batch_remit.bank_deposit_number,
1173                  cr.reference_type,
1174                  cr.reference_id,
1175                  cr.customer_receipt_reference,
1176                  cba.bank_account_name  ;
1177         l_total_discount  NUMBER ;
1178         l_period_name     VARCHAR2(15) ;
1179         l_status          BOOLEAN ;
1180 
1181         BEGIN
1182 
1183             FOR select_header IN header_cursor ( p_customer_trx_id )
1184             LOOP
1185             -- Collect Statistics
1186 
1187                  l_period_name := get_period_name ( select_header.gl_date ) ;
1188 
1189                  BEGIN
1190 
1191                      INSERT INTO ar_archive_header
1192                      ( archive_id,
1193                        transaction_class,
1194                        transaction_type,
1195                        transaction_id,
1196                        related_transaction_class,
1197                        related_transaction_type,
1198                        related_transaction_id,
1199                        transaction_number,
1200                        transaction_date,
1201                        batch_name,
1202                        batch_source_name,
1203                        set_of_books_name,
1204                        amount,
1205                        -- acctd_amount, -- bug1199027
1206                        exchange_gain_loss,
1207                        earned_discount_taken,
1208                        unearned_discount_taken,
1209                        -- acctd_earned_discount_taken, -- bug1199027
1210                        -- acctd_unearned_discount_taken, -- bug1199027
1211                        type,
1212                        adjustment_type,
1213                        post_to_gl,
1214                        accounting_affect_flag,
1215                        cash_receipt_status,
1216                        cash_receipt_history_status,
1217                        reason_code_meaning,
1218                        bill_to_customer_name,
1219                        bill_to_customer_number,
1220                        bill_to_customer_location,
1221                        bill_to_customer_address1,
1222                        bill_to_customer_address2,
1223                        bill_to_customer_address3,
1224                        bill_to_customer_address4,
1225                        bill_to_customer_city,
1226                        bill_to_customer_state,
1227                        bill_to_customer_country,
1228                        bill_to_customer_postal_code,
1229                        ship_to_customer_name,
1230                        ship_to_customer_number,
1231                        ship_to_customer_location,
1232                        ship_to_customer_address1,
1233                        ship_to_customer_address2,
1234                        ship_to_customer_address3,
1235                        ship_to_customer_address4,
1236                        ship_to_customer_city,
1237                        ship_to_customer_state,
1238                        ship_to_customer_country,
1239                        ship_to_customer_postal_code,
1240                        remit_to_address1,
1241                        remit_to_address2,
1242                        remit_to_address3,
1243                        remit_to_address4,
1244                        remit_to_city,
1245                        remit_to_state,
1246                        remit_to_country,
1247                        remit_to_postal_code,
1248                        salesrep_name,
1249                        term_name,
1250                        term_due_date,
1251                        printing_last_printed,
1252                        printing_option,
1253                        purchase_order,
1254                        comments,
1255                        exchange_rate_type,
1256                        exchange_rate_date,
1257                        exchange_rate,
1258                        currency_code,
1259                        gl_date,
1260                        reversal_date,
1261                        reversal_category,
1262                        reversal_reason_code_meaning,
1263                        reversal_comments,
1264                        attribute_category,
1265                        attribute1,
1266                        attribute2,
1267                        attribute3,
1268                        attribute4,
1269                        attribute5,
1270                        attribute6,
1271                        attribute7,
1272                        attribute8,
1273                        attribute9,
1274                        attribute10,
1275                        attribute11,
1276                        attribute12,
1277                        attribute13,
1278                        attribute14,
1279                        attribute15,
1280                        receipt_method_name,
1281                        waybill_number,
1282                        document_sequence_name,
1283                        document_sequence_value,
1284                        start_date_commitment,
1285                        end_date_commitment,
1286                        invoicing_rule_name,
1287                        customer_bank_account_name,
1288                        deposit_date,
1289                        factor_discount_amount,
1290                        interface_header_context,
1291                        interface_header_attribute1,
1292                        interface_header_attribute2,
1293                        interface_header_attribute3,
1294                        interface_header_attribute4,
1295                        interface_header_attribute5,
1296                        interface_header_attribute6,
1297                        interface_header_attribute7,
1298                        interface_header_attribute8,
1299                        interface_header_attribute9,
1300                        interface_header_attribute10,
1301                        interface_header_attribute11,
1302                        interface_header_attribute12,
1303                        interface_header_attribute13,
1304                        interface_header_attribute14,
1305                        interface_header_attribute15,
1306                        bank_deposit_number,
1307                        reference_type,
1308                        reference_id,
1309                        customer_receipt_reference,
1310                        bank_account_name
1311                      )
1312                      VALUES
1313                      ( lpad(p_archive_id,14,'0'), /* modified for bug 3266428 */
1314                        select_header.type,
1315                        select_header.name,
1316                        select_header.trx_id,
1317                        select_header.related_trx_type,
1318                        select_header.related_trx_id,
1319                        select_header.prev_trx_id ,
1320                        select_header.trx_number,
1321                        select_header.trx_date,
1322                        select_header.batch_name,
1323                        select_header.batch_source_name,
1324                        select_header.sob_name,
1325                        select_header.amount,
1326                        -- select_header.acctd_amount, --bug1199027
1327                        select_header.exch_gain_loss,
1328                        select_header.earned_disc_taken,
1329                        select_header.unearned_disc_taken,
1330                        -- select_header.acctd_earned_disc_taken, --bug1199027
1331                        -- select_header.acctd_unearned_disc_taken, --bug1199027
1332                        select_header.adj_trx_type,
1333                        select_header.adj_type,
1334                        select_header.post_to_gl,
1335                        select_header.open_receivable,
1336                        select_header.cash_rcpt_status,
1337                        select_header.cash_rcpt_hist_status,
1338                        select_header.reason_code,
1339                        select_header.bill_to_cust_name,
1340                        select_header.bill_to_cust_no,
1341                        select_header.bill_to_cust_loc,
1342                        select_header.bill_to_cust_addr1,
1343                        select_header.bill_to_cust_addr2,
1344                        select_header.bill_to_cust_addr3,
1345                        select_header.bill_to_cust_addr4,
1346                        select_header.bill_to_cust_city,
1347                        select_header.bill_to_cust_state,
1348                        select_header.bill_to_cust_country,
1349                        select_header.bill_to_cust_zip,
1350                        select_header.ship_to_cust_name,
1351                        select_header.ship_to_cust_no,
1352                        select_header.ship_to_cust_loc,
1353                        select_header.ship_to_cust_addr1,
1354                        select_header.ship_to_cust_addr2,
1355                        select_header.ship_to_cust_addr3,
1356                        select_header.ship_to_cust_addr4,
1357                        select_header.ship_to_cust_city,
1358                        select_header.ship_to_cust_state,
1359                        select_header.ship_to_cust_country,
1360                        select_header.ship_to_cust_zip,
1361                        select_header.remit_to_cust_addr1,
1362                        select_header.remit_to_cust_addr2,
1363                        select_header.remit_to_cust_addr3,
1364                        select_header.remit_to_cust_addr4,
1365                        select_header.remit_to_cust_city,
1366                        select_header.remit_to_cust_state,
1367                        select_header.remit_to_cust_country,
1368                        select_header.remit_to_cust_zip,
1369                        select_header.salesrep_name,
1370                        select_header.term_name,
1371                        select_header.term_due_date,
1372                        select_header.last_printed,
1373                        select_header.printing_option,
1374                        select_header.purchase_order,
1375                        select_header.comments,
1376                        select_header.exch_rate_type,
1377                        select_header.exch_date,
1378                        select_header.exch_rate,
1379                        select_header.curr_code,
1380                        select_header.gl_date,
1381                        select_header.reversal_date,
1382                        select_header.reversal_category,
1383                        select_header.reversal_reason_code,
1384                        select_header.reversal_comments,
1385                        select_header.attr_category,
1386                        select_header.attr1,
1387                        select_header.attr2,
1388                        select_header.attr3,
1389                        select_header.attr4,
1390                        select_header.attr5,
1391                        select_header.attr6,
1392                        select_header.attr7,
1393                        select_header.attr8,
1394                        select_header.attr9,
1395                        select_header.attr10,
1396                        select_header.attr11,
1397                        select_header.attr12,
1398                        select_header.attr13,
1399                        select_header.attr14,
1400                        select_header.attr15,
1401                        select_header.rcpt_method,
1402                        select_header.waybill_no,
1403                        select_header.doc_name,
1404                        select_header.doc_seq_value,
1405                        select_header.st_date_commitment,
1406                        select_header.en_date_commitment,
1407                        select_header.invoicing_rule,
1408                        select_header.bank_acct_name,
1409                        select_header.deposit_date,
1410                        select_header.factor_disc_amount,
1411                        select_header.int_hdr_context,
1412                        select_header.int_hdr_attr1,
1413                        select_header.int_hdr_attr2,
1414                        select_header.int_hdr_attr3,
1415                        select_header.int_hdr_attr4,
1416                        select_header.int_hdr_attr5,
1417                        select_header.int_hdr_attr6,
1418                        select_header.int_hdr_attr7,
1419                        select_header.int_hdr_attr8,
1420                        select_header.int_hdr_attr9,
1421                        select_header.int_hdr_attr10,
1422                        select_header.int_hdr_attr11,
1423                        select_header.int_hdr_attr12,
1424                        select_header.int_hdr_attr13,
1425                        select_header.int_hdr_attr14,
1426                        select_header.int_hdr_attr15,
1427                        select_header.bank_deposit_no,
1428                        select_header.reference_type,
1429                        select_header.reference_id,
1430                        select_header.cust_rcpt_reference,
1431                        select_header.bank_acct_name2
1432                      ) ;
1433 
1434                      -- bug1199027
1435                      l_status := ins_control_detail_table ( NVL(select_header.acctd_amount,0),
1436                                                            select_header.type,
1437                                                            NVL(select_header.open_receivable,'Y'),
1438                                                            l_period_name,
1439                                                            p_archive_id  ) ;
1440 
1441                      IF select_header.type = 'CASH'
1442                      THEN
1443                         l_total_discount := NVL(select_header.acctd_earned_disc_taken,0) +
1444                                                  NVL(select_header.acctd_unearned_disc_taken,0);
1445                         IF l_total_discount IS NOT NULL
1446                         THEN
1447                             -- bug1199027
1448                             l_status := ins_control_detail_table ( l_total_discount,
1449                                                                   'DISC',
1450                                                                   NVL(select_header.open_receivable,'Y'),
1451                                                                   l_period_name,
1452                                                                   p_archive_id  ) ;
1453                         END IF ;
1454                         --
1455                         IF select_header.exch_gain_loss IS NOT NULL
1456                         THEN
1457                             -- bug1199027
1458                             l_status := ins_control_detail_table ( select_header.exch_gain_loss,
1459                                                                   'EXCH',
1460                                                                   NVL(select_header.open_receivable,'Y'),
1461                                                                   l_period_name,
1462                                                                   p_archive_id  ) ;
1463                         END IF ;
1464                      END IF ;
1465 
1466                  EXCEPTION
1467                      WHEN OTHERS THEN
1468                          print( 1, 'Failed while inserting into AR_ARCHIVE_HEADER') ;
1469                          print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
1470                          RAISE ;
1471                  END ;
1472 
1473             END LOOP ;
1474 
1475             RETURN ( TRUE );
1476 
1477         EXCEPTION
1478             WHEN OTHERS THEN
1479                 print( 1, '  ...Failed while inserting into AR_ARCHIVE_HEADER');
1480                 print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
1481                 RAISE ;
1482         END ;
1483     END ;
1484 
1485     --
1486     -- Insert into archive_detail
1487     --
1488     FUNCTION archive_detail( p_customer_trx_id IN NUMBER     ,
1489                              p_archive_level   IN VARCHAR2   ,
1490                              p_archive_id      IN NUMBER     ) RETURN BOOLEAN  IS
1491         CURSOR detail_cursor ( cp_customer_trx_id NUMBER ,
1492                                cp_archive_level   VARCHAR2 ,
1493                                cp_org_profile     VARCHAR2 ) IS
1494         SELECT
1495         ctt.type       trx_class,			/* transaction_class */
1496         ctt.name       trx_type,			/* transaction_type */
1497         ct.customer_trx_id trx_id, 		/* transaction_id */
1498         ctl.customer_trx_line_id line_id,	/* transaction_line_id */
1499         decode(ctt.type, 		/* related_transaction_class */
1500             'CM', ctt_prev.type) related_trx_class,
1501         decode(ctt.type,'CM', ctt_prev.name)
1502             related_trx_type,	/* related_transaction_type */
1503         decode(ctt.type,'CM', ct.previous_customer_trx_id)
1504             related_trx_id,	/* related_transaction_id */
1505         decode(ctt.type, 'CM', ctl.previous_customer_trx_line_id)
1506             related_trx_line_id,  /* related_transaction_line_id */
1507         ctl.line_number line_number,
1508         'LINE' dist_type, 			/* distribution_type */
1509         '' app_type,				/* application_type */
1510         lu_line.meaning line_code_meaning,		/* line_code_meaning */
1511         ctl.description description,
1512         /* item_name */
1513         rtrim( mtl.segment1 || '.' ||
1514             mtl.segment2 || '.' ||
1515             mtl.segment3 || '.' ||
1516             mtl.segment4 || '.' ||
1517             mtl.segment5 || '.' ||
1518             mtl.segment6 || '.' ||
1519             mtl.segment7 || '.' ||
1520             mtl.segment8 || '.' ||
1521             mtl.segment9 || '.' ||
1522             mtl.segment10|| '.' ||
1523             mtl.segment11|| '.' ||
1524             mtl.segment12|| '.' ||
1525             mtl.segment13|| '.' ||
1526             mtl.segment14|| '.' ||
1527             mtl.segment15|| '.' ||
1528             mtl.segment16|| '.' ||
1529             mtl.segment17|| '.' ||
1530             mtl.segment18|| '.' ||
1531             mtl.segment19|| '.' ||
1532             mtl.segment20, '.' ) item_name,
1533         nvl(ctl.quantity_invoiced, ctl.quantity_credited) qty, /* qty */
1534         ctl.unit_selling_price selling_price,
1535         ctl.line_type line_type,
1536         ctl.attribute_category attr_category,
1537         ctl.attribute1 attr1,
1538         ctl.attribute2 attr2,
1539         ctl.attribute3 attr3,
1540         ctl.attribute4 attr4,
1541         ctl.attribute5 attr5,
1542         ctl.attribute6 attr6,
1543         ctl.attribute7 attr7,
1544         ctl.attribute8 attr8,
1545         ctl.attribute9 attr9,
1546         ctl.attribute10 attr10,
1547         ctl.attribute11 attr11,
1548         ctl.attribute12 attr12,
1549         ctl.attribute13 attr13,
1550         ctl.attribute14 attr14,
1551         ctl.attribute15 attr15,
1552         ctl.extended_amount amount,		        /* amount */
1553         to_number('') acctd_amount,			/* acctd_amount */
1554         ctl.uom_code uom_code,
1555         '' ussgl_trx_code,				/* ussgl_transaction_code */
1556         ctl.tax_rate tax_rate,
1557         vt.tax_code tax_code,
1558         ctl.tax_precedence tax_precedence,
1559         to_number('') ccid1,  	/* account_ccid1 */
1560         to_number('') ccid2, 	/* account_ccid2 */
1561         to_number('') ccid3, 	/* account_ccid3 */
1562         to_number('') ccid4, 	/* account_ccid4 */
1563         to_date(NULL) gl_date,	/* gl_date */
1564         to_date(NULL) gl_posted_date, /* gl_posted_date */
1565         rule1.name rule_name,	    /* accounting_rule_name */
1566         ctl.accounting_rule_duration acctg_rule_duration,
1567         ctl.rule_start_date rule_start_date,
1568         ctl.last_period_to_credit last_period_to_credit,
1569         '' line_comment,  	/* line_comment */
1570         to_number('') line_adjusted,	/* line_adjusted */
1571         to_number('') freight_adjusted, /* freight_adjusted */
1572         to_number('') tax_adjusted,	/* tax_adjusted */
1573         to_number('') charges_adjusted, /* receivables_charges_adjusted */
1574         to_number('') line_applied,	/* line_applied */
1575         to_number('') freight_applied,	/* freight_applied */
1576         to_number('') tax_applied,	/* tax_applied */
1577         to_number('') charges_applied,	/* receivables_charges_applied */
1578         to_number('') earned_disc_taken,/* earned_discount_taken */
1579         to_number('') unearned_disc_taken,      /* unearned_discount_taken */
1580         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
1581         to_number('') acctd_amount_applied_to,	/* acctd_amount_applied_to */
1582         to_number('') acctd_earned_disc_taken,	/* acctd_earned_disc_taken */
1583         to_number('') acctd_unearned_disc_taken,	/* acctd_unearned_disc_taken */
1584         to_number('') factor_discount_amount,	/* factor_discount_amount */
1585         to_number('') acctd_factor_discount_amount,	/* acctd_factor_discount_amount */
1586         ctl.interface_line_context int_line_context,
1587         ctl.interface_line_attribute1 int_line_attr1,
1588         ctl.interface_line_attribute2 int_line_attr2,
1589         ctl.interface_line_attribute3 int_line_attr3,
1590         ctl.interface_line_attribute4 int_line_attr4,
1591         ctl.interface_line_attribute5 int_line_attr5,
1592         ctl.interface_line_attribute6 int_line_attr6,
1593         ctl.interface_line_attribute7 int_line_attr7,
1594         ctl.interface_line_attribute8 int_line_attr8,
1595         ctl.interface_line_attribute9 int_line_attr9,
1596         ctl.interface_line_attribute10 int_line_attr10,
1597         ctl.interface_line_attribute11 int_line_attr11,
1598         ctl.interface_line_attribute12 int_line_attr12,
1599         ctl.interface_line_attribute13 int_line_attr13,
1600         ctl.interface_line_attribute14 int_line_attr14,
1601         ctl.interface_line_attribute15 int_line_attr15,
1602         '' exch_rate_type,			/* exchange_rate_type */
1603         to_date(NULL) exch_date,			/* exchange_rate_date */
1604         to_number('') exch_rate, 		/* exchange_rate */
1605         to_date(NULL) due_date,			/* due_date */
1606         to_date(NULL) apply_date,			/* apply_date */
1607         ctl.movement_id movement_id,
1608         ctl.tax_vendor_return_code vendor_return_code,
1609         /* tax_authorities_tax_rate */
1610         rtrim( to_char(st.location1_rate) || ' ' ||
1611         to_char(st.location2_rate) || ' ' ||
1612         to_char(st.location3_rate) || ' ' ||
1613         to_char(st.location4_rate) || ' ' ||
1614         to_char(st.location5_rate) || ' ' ||
1615         to_char(st.location6_rate) || ' ' ||
1616         to_char(st.location7_rate) || ' ' ||
1617         to_char(st.location8_rate) || ' ' ||
1618         to_char(st.location9_rate) || ' ' ||
1619         to_char(st.location10_rate), ' ' ) tax_auth_tax_rate,
1620         ctl.tax_exempt_flag tax_exempt_flag,
1621         ctl.tax_exemption_id tax_exemption_id,
1622         te.exemption_type exemption_type,
1623         nvl(lu_te.meaning, lu_line2.meaning) tax_exemption_reason,/* tax_exemption_reason */
1624         nvl(te.customer_exemption_number, ctl.tax_exempt_number)
1625              tax_exemption_number, /* tax_exemption_number */
1626         /* item_exception_rate */
1627         rtrim( to_char(ier.location1_rate) || ' ' ||
1628         to_char(ier.location2_rate) || ' ' ||
1629         to_char(ier.location3_rate) || ' ' ||
1630         to_char(ier.location4_rate) || ' ' ||
1631         to_char(ier.location5_rate) || ' ' ||
1632         to_char(ier.location6_rate) || ' ' ||
1633         to_char(ier.location7_rate) || ' ' ||
1634         to_char(ier.location8_rate) || ' ' ||
1635         to_char(ier.location9_rate) || ' ' ||
1636         to_char(ier.location10_rate), ' ' ) item_exception_rate ,
1637         lu_ier.meaning meaning,			/* exception_reason */
1638         dl.original_collectibility_flag,      /* original_collectibility_flag */
1639         dl.line_collectible_flag,             /* line_collectible_flag */
1640         dl.manual_override_flag,              /* manual_override_flag */
1641         ''   contingency_code,  	/* contingency_code */
1642         to_date(null) expiration_date,  /* expiration_date */
1643         to_number('') expiration_days,  /* expiration_days */
1644         ctl.override_auto_accounting_flag	/* override_auto_accounting_flag */
1645         FROM
1646         ar_lookups lu_te,
1647         ra_tax_exemptions te,
1648         ar_lookups lu_ier,
1649         ra_item_exception_rates ier,
1650         ar_sales_tax      st,
1651         ar_vat_tax        vt,
1652         ar_lookups        lu_line,
1653         ar_lookups        lu_line2,
1654         ra_rules          rule1,
1655         ra_cust_trx_types ctt_prev,
1656         ra_cust_trx_types ctt,
1657         mtl_system_items  mtl,
1658         ra_customer_trx_lines    ctl,
1659         ra_customer_trx   ct_prev,
1660         ra_customer_trx   ct,
1661 	ar_deferred_lines dl
1662         WHERE te.tax_exemption_id (+) = ctl.tax_exemption_id
1663         AND   te.reason_code = lu_te.lookup_code (+)
1664         AND   lu_te.lookup_type (+) = 'TAX_REASON'
1665         AND   ier.item_exception_rate_id (+) = ctl.item_exception_rate_id
1666         AND   ier.reason_code = lu_ier.lookup_code (+)
1667         AND   lu_ier.lookup_type (+) = 'TAX_EXCEPTION_REASON'
1668         AND   st.sales_tax_id (+)    = ctl.sales_tax_id
1669         AND   vt.vat_tax_id (+)      = ctl.vat_tax_id
1670         AND   lu_line.lookup_code (+)    = ctl.reason_code
1671         AND   lu_line.lookup_type (+)    = 'INVOICING_REASON'
1672         AND   lu_line2.lookup_code (+)    = ctl.tax_exempt_reason_code
1673         AND   lu_line2.lookup_type (+)    = 'TAX_REASON'
1674         AND   rule1.rule_id (+)        = ctl.accounting_rule_id
1675         AND   ctt.cust_trx_type_id    = ct.cust_trx_type_id
1676         AND   mtl.inventory_item_id (+) = ctl.inventory_item_id
1677         AND   mtl.organization_id (+) = to_number(cp_org_profile)
1678         AND   ctl.customer_trx_id = ct.customer_trx_id
1679         AND   ct.previous_customer_trx_id = ct_prev.customer_trx_id(+)
1680         AND   ct_prev.cust_trx_type_id = ctt_prev.cust_trx_type_id(+)
1681         AND   ct.customer_trx_id     = cp_customer_trx_id
1682         AND   cp_archive_level <> 'H'
1683         AND   ctl.customer_trx_line_id = dl.customer_trx_line_id(+)
1684         UNION ALL /* Bug 5105156 - fix 5044763 */
1685         ---------------------------------------------------------------------
1686         -- TRX distributions
1687         -- 'A' level only
1688         ---------------------------------------------------------------------
1689         SELECT
1690         ctt.type trx_class,			/* transaction_class */
1691         ctt.name trx_type,			/* transaction_type */
1692         ct.customer_trx_id trx_id, 		/* transaction_id */
1693         ctlgd.customer_trx_line_id line_id,	/* transaction_line_id */
1694         '' related_trx_class,			/* related_transaction_class */
1695         '' related_trx_type,			/* related_transaction_type */
1696         to_number('') related_trx_id, 		/* related_transaction_id */
1697         to_number('') related_trx_line_id,	/* related_transaction_line_id */
1698         to_number('') line_number,		/* line_number */
1699         ctlgd.account_class dist_type, 		/* distribution_type */
1700         '' app_type,				/* application_type */
1701         '' line_code_meaning, 			/* line_code_meaning */
1702         '' description,                         /* description */
1703         '' item_name,                           /* item_name */
1704         to_number('') qty, 			/* qty */
1705         to_number('') selling_price,		/* unit_selling_price */
1706         '' line_type,				/* line_type */
1707         ctlgd.attribute_category attr_category,
1708         ctlgd.attribute1 attr1,
1709         ctlgd.attribute2 attr2,
1710         ctlgd.attribute3 attr3,
1711         ctlgd.attribute4 attr4,
1712         ctlgd.attribute5 attr5,
1713         ctlgd.attribute6 attr6,
1714         ctlgd.attribute7 attr7,
1715         ctlgd.attribute8 attr8,
1716         ctlgd.attribute9 attr9,
1717         ctlgd.attribute10 attr10,
1718         ctlgd.attribute11 attr11,
1719         ctlgd.attribute12 attr12,
1720         ctlgd.attribute13 attr13,
1721         ctlgd.attribute14 attr14,
1722         ctlgd.attribute15 attr15,
1723         ctlgd.amount amount,
1724         ctlgd.acctd_amount acctd_amount,
1725         '' uom_code,		 /* uom code */
1726         ctlgd.ussgl_transaction_code ussgl_trx_code,
1727         to_number('') tax_rate,			/* tax_rate */
1728         '' tax_code, 				/* tax_code */
1729         to_number('') tax_precedence,		/* tax_precedence */
1730         ctlgd.code_combination_id ccid1,        /* account_ccid1 */
1731         to_number('') ccid2, 		/* account_ccid2 */
1732         to_number('') ccid3, 		/* account_ccid3 */
1733         to_number('') ccid4, 		/* account_ccid4 */
1734         nvl(ctlgd.gl_date, ct.trx_date) gl_date,/* gl_date */
1735         ctlgd.gl_posted_date gl_posted_date,	/* gl_posted_date */
1736         '' acctg_rule_name,			/* accounting_rule_name */
1737         to_number('') acctg_rule_duration,	/* accounting_rule_duration */
1738         to_date(NULL) rule_start_date,		/* rule_start_date */
1739         to_number('') last_period_to_credit,	/* last_period_to_credit */
1740         '' line_amount,  			/* line_comment */
1741         to_number('') line_adjusted,		/* line_adjusted */
1742         to_number('') freight_adjusted,	        /* freight_adjusted */
1743         to_number('') tax_adjusted,		/* tax_adjusted */
1744         to_number('') charges_adjusted,	        /* receivables_charges_adjusted */
1745         to_number('') line_applied,		/* line_applied */
1746         to_number('') freight_applied,		/* freight_applied */
1747         to_number('') tax_applied,		/* tax_applied */
1748         to_number('') charges_applied,		/* receivables_charges_applied */
1749         to_number('') earned_disc_taken,	/* earned_discount_taken */
1750         to_number('') unearned_disc_taken,	/* unearned_discount_taken */
1751         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
1752         to_number('') acctd_amount_applied_to,	/* acctd_amount_applied_to */
1753         to_number('') acctd_earned_disc_taken,	/* acctd_earned_disc_taken */
1754         to_number('') acctd_unearned_disc_taken,/* acctd_unearned_disc_taken */
1755         to_number('') factor_discount_amount,	/* factor_discount_amount */
1756         to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
1757         '' int_line_context, /* interface_line_context */
1758         '' int_line_attr1,   /* interface_line_attribute1 */
1759         '' int_line_attr2,   /* interface_line_attribute2 */
1760         '' int_line_attr3,   /* interface_line_attribute3 */
1761         '' int_line_attr4,   /* interface_line_attribute4 */
1762         '' int_line_attr5,   /* interface_line_attribute5 */
1763         '' int_line_attr6,   /* interface_line_attribute6 */
1764         '' int_line_attr7,   /* interface_line_attribute7 */
1765         '' int_line_attr8,   /* interface_line_attribute8 */
1766         '' int_line_attr9,		/* interface_line_attribute9 */
1767         '' int_line_attr10,		/* interface_line_attribute10 */
1768         '' int_line_attr11,		/* interface_line_attribute11 */
1769         '' int_line_attr12,		/* interface_line_attribute12 */
1770         '' int_line_attr13,		/* interface_line_attribute13 */
1771         '' int_line_attr14,		/* interface_line_attribute14 */
1772         '' int_line_attr15,		/* interface_line_attribute15 */
1773         '' exchange_rate_type,		/* exchange_rate_type */
1774         to_date(NULL) exch_date,		/* exchange_rate_date */
1775         to_number('') exch_rate, 	/* exchange_rate */
1776         to_date(NULL) due_date,		/* due_date */
1777         to_date(NULL) apply_date,	        /* apply_date */
1778         to_number('') movement_id,	/* movement_id */
1779         '' tax_vendor_return_code,	/* tax_vendor_return_code */
1780         '' tax_auth_tax_rate,  	        /* tax_authorities_tax_rate */
1781         '' tax_exempt_flag,		/* tax_exemption_flag */
1782         to_number('') tax_exemption_id, /* tax_exemption_id */
1783         '' exemption_type,		/* exemption_type */
1784         '' tax_exemption_reason,	/* exemption_reason */
1785         '' tax_exemption_number,	/* customer_exemption_number */
1786         '' item_exception_rate,  	/* item_exception_rate */
1787         '' meaning,			/* exception_reason */
1788         '',                             /* original_collectibility_flag */
1789         '',                             /* line_collectible_flag */
1790         '',                             /* manual_override_flag */
1791         '',                             /* contingency_code */
1792         to_date(null),                  /* expiration_date */
1793         to_number(null),                /* expiration_days */
1794 	''			/* override_auto_accounting_flag */
1795         FROM
1796         ra_cust_trx_types ctt,
1797         ra_cust_trx_line_gl_dist ctlgd,
1798         ra_customer_trx   ct
1799         WHERE  ctt.cust_trx_type_id  = ct.cust_trx_type_id
1800         AND    ctlgd.customer_trx_id = ct.customer_trx_id
1801         AND    ctlgd.account_set_flag <> 'Y'  /* no acount sets */
1802         AND    decode(ctlgd.account_class, 'REC',
1803                    ctlgd.latest_rec_flag, 'Y') = 'Y'
1804         AND    ct.customer_trx_id     = cp_customer_trx_id
1805         AND    cp_archive_level = 'A'
1806         UNION ALL /* Bug 5105156 - fix 5044763 */
1807         ---------------------------------------------------------------------
1808                -- TRX adjustments (ADJ)
1809                -- 'L', 'A' levels
1810         ---------------------------------------------------------------------
1811         SELECT
1812         'ADJ' trx_class,  	        /* transaction_class */
1813         ''    trx_type,    	        /* transaction_type */
1814         adj.adjustment_id trx_id, 	/* transaction_id */
1815         to_number('') line_id,		/* transaction_line_id */
1816         ctt.type related_trx_class,		/* related_transaction_class */
1817         ctt.name related_trx_type,		/* related_transaction_type */
1818         ct.customer_trx_id related_trx_id, 	/* related_transaction_id */
1819         to_number('') related_trx_line_id,		/* related_transaction_line_id */
1820         to_number('') line_number, 	/* line_number */
1821         'ADJ' dist_type, 		/* distribution_type */
1822         '' app_type,			/* application_type */
1823         '' line_code_meaning, 			/* line_code_meaning */
1824         '' description,			/* description */
1825         '' item_name,			/* item_name */
1826         to_number('') qty,		/* quantity */
1827         to_number('') selling_price,	/* unit_selling_price */
1828         '' line_type,			/* line_type */
1829         adj.attribute_category attr_category,
1830         adj.attribute1 attr1,
1831         adj.attribute2 attr2,
1832         adj.attribute3 attr3,
1833         adj.attribute4 attr4,
1834         adj.attribute5 attr5,
1835         adj.attribute6 attr6,
1836         adj.attribute7 attr7,
1837         adj.attribute8 attr8,
1838         adj.attribute9 attr9,
1839         adj.attribute10 attr10,
1840         adj.attribute11 attr11,
1841         adj.attribute12 attr12,
1842         adj.attribute13 attr13,
1843         adj.attribute14 attr14,
1844         adj.attribute15 attr15,
1845         adj.amount amount,
1846         adj.acctd_amount acctd_amount,
1847         '' uom_code,		/* uom_code */
1848         '' ussgl_trx_code,	/* ussgl_transaction_code */
1849         to_number('') tax_rate,/* tax_rate */
1850         '' tax_code,		/* tax_code */
1851         to_number('') tax_precedence,	/* tax_precedence */
1852         adj.code_combination_id ccid1, 	/* account_ccid1 */
1853         to_number('') ccid2,	/* account_ccid2 */
1854         to_number('') ccid3,	/* account_ccid3 */
1855         to_number('') ccid4,	/* account_ccid4 */
1856         adj.gl_date gl_date,
1857         adj.gl_posted_date gl_posted_date,
1858         '' acctg_rule_duration,	/* acct_rule_name */
1859         to_number('') rule_name, /* rule_duration */
1860         to_date(NULL) rule_start_date,	/* rule_start_date */
1861         to_number('') last_period_to_credit,	/* last_period_to_credit */
1862         '' line_comment,  		/* line_comment */
1863         adj.line_adjusted line_adjusted,	/* line_adjusted */
1864         adj.freight_adjusted freight_adjusted,	/* freight_adjusted */
1865         adj.tax_adjusted tax_adjusted,	/* tax_adjusted */
1866         adj.receivables_charges_adjusted charges_adjusted, /* receivables_charges_adjusted */
1867         to_number('') line_applied,		/* line_applied */
1868         to_number('') freight_applied,		/* freight_applied */
1869         to_number('') tax_applied,		/* tax_applied */
1870         to_number('') charges_applied,		/* receivables_charges_applied */
1871         to_number('') earned_disc_taken,	/* earned_discount_taken */
1872         to_number('') unearned_disc_taken,	/* unearned_discount_taken */
1873         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
1874         to_number('') acctd_amount_applied_to,	 /* acctd_amount_applied_to */
1875         to_number('') acctd_earned_disc_taken,		/* acctd_earned_disc_taken */
1876         to_number('') acctd_unearned_disc_taken,	/* acctd_unearned_disc_taken */
1877         to_number('') factor_discount_amount,		/* factor_discount_amount */
1878         to_number('') acctd_factor_discount_amount,	/* acctd_factor_discount_amount */
1879         '' int_line_context,  	/* interface_line_context */
1880         '' int_line_attr1,  	/* interface_line_attribute1 */
1881         '' int_line_attr2,  	/* interface_line_attribute2 */
1882         '' int_line_attr3,   	/* interface_line_attribute3 */
1883         '' int_line_attr4,  	/* interface_line_attribute4 */
1884         '' int_line_attr5,  	/* interface_line_attribute5 */
1885         '' int_line_attr6,   	/* interface_line_attribute6 */
1886         '' int_line_attr7,   	/* interface_line_attribute7 */
1887         '' int_line_attr8,   	/* interface_line_attribute8 */
1888         '' int_line_attr9,   	/* interface_line_attribute9 */
1889         '' int_line_attr10,   	/* interface_line_attribute10 */
1890         '' int_line_attr11,   	/* interface_line_attribute11 */
1891         '' int_line_attr12,   	/* interface_line_attribute12 */
1892         '' int_line_attr13,   	/* interface_line_attribute13 */
1893         '' int_line_attr14,   	/* interface_line_attribute14 */
1894         '' int_line_attr15,    /* interface_line_attribute15 */
1895         '' exch_rate_type, 	/* exchange_rate_type */
1896         to_date(NULL) exch_date,	/* exchange_rate_date */
1897         to_number('') exch_rate,/* exchange_rate */
1898         to_date(NULL) due_date,		/* due_date */
1899         to_date(NULL) apply_date,	/* apply_date */
1900         to_number('') movement_id,	/* movement_id */
1901         '' vendor_return_code,		/* tax_vendor_return_code */
1902         '' tax_auth_tax_rate,		/* tax_authority_tax_rates */
1903         '' tax_exempt_flag,		/* tax_exemption_flag */
1904         to_number('') tax_exemption_id,/* tax_exemption_id */
1905         '' exemption_type,		/* exemption_type */
1906         '' tax_exemption_reason,	/* exemption_reason */
1907         '' tax_exemption_number,	/* customer_exemption_number */
1908         '' item_exception_rate,	/* item_exception_rate */
1909         '' meaning,			/* item_exception_reason */
1910         '',                             /* original_collectibility_flag */
1911         '',                             /* line_collectible_flag */
1912         '',                             /* manual_override_flag */
1913         '',                             /* contingency_code */
1914         to_date(null),                  /* expiration_date */
1915         to_number(null),                /* expiration_days */
1916 	''			/* override_auto_accounting_flag */
1917         FROM   ra_cust_trx_types ctt,
1918                ra_customer_trx   ct,
1919                ar_adjustments    adj
1920         WHERE  adj.customer_trx_id     = cp_customer_trx_id
1921         and    adj.customer_trx_id     = ct.customer_trx_id
1922         and    ctt.cust_trx_type_id    = ct.cust_trx_type_id
1923         and    cp_archive_level <> 'H'
1924 	UNION ALL /* Bug 5105156 - fix 5044763 */
1925 	---------------------------------------------------------------------
1926         -- TRX contingencies (CONTINGENCY)
1927         -- 'L', 'A' levels
1928 	---------------------------------------------------------------------
1929 	SELECT
1930 	'CONTINGENCY',			/* transaction_class */
1931 	'', 				/* transaction_type */
1932 	ctl.customer_trx_id,		/* transaction_id */
1933 	ctl.customer_trx_line_id,	/* transaction_line_id */
1934 	'',				/* related_transaction_class */
1935 	'',				/* related_transaction_type */
1936 	to_number(''),			/* related_transaction_id */
1937 	to_number(''),			/* related_transaction_line_id */
1938 	to_number(''), 			/* line_number */
1939 	'', 				/* distribution_type */
1940         '',				/* application_type */
1941 	'', 				/* line_code_meaning */
1942 	'',				/* description */
1943 	'',				/* item_name */
1944 	to_number(''),			/* quantity */
1945 	to_number(''),			/* unit_selling_price */
1946 	'',				/* line_type */
1947 	'',
1948 	'',
1949 	'',
1950 	'',
1951 	'',
1952 	'',
1953 	'',
1954 	'',
1955 	'',
1956 	'',
1957 	'',
1958 	'',
1959 	'',
1960 	'',
1961 	'',
1962 	'',
1963 	to_number(''),
1964 	to_number(''),
1965 	'',				/* uom_code */
1966 	'',				/* ussgl_transaction_code */
1967 	to_number(''),			/* tax_rate */
1968 	'',				/* tax_code */
1969 	to_number(''),			/* tax_precedence */
1970 	to_number(''), 			/* account_ccid1 */
1971 	to_number(''),			/* account_ccid2 */
1972 	to_number(''),			/* account_ccid3 */
1973 	to_number(''),			/* account_ccid4 */
1974 	to_date(null),
1975 	to_date(null),
1976         '',				/* acct_rule_name */
1977         to_number(''), 			/* rule_duration */
1978         to_date(null),			/* rule_start_date */
1979         to_number(''),			/* last_period_to_credit */
1980         '',  				/* line_comment */
1981 	to_number(''),			/* line_adjusted */
1982 	to_number(''),			/* freight_adjusted */
1983 	to_number(''),			/* tax_adjusted */
1984 	to_number(''),			/* receivables_charges_adjusted */
1985 	to_number(''),			/* line_applied */
1986 	to_number(''),			/* freight_applied */
1987 	to_number(''),			/* tax_applied */
1988 	to_number(''),			/* receivables_charges_applied */
1989 	to_number(''),			/* earned_discount_taken */
1990 	to_number(''),			/* unearned_discount_taken */
1991 	to_number(''),			/* acctd_amount_applied_from */
1992 	to_number(''),			/* acctd_amount_applied_to */
1993 	to_number(''),			/* acctd_earned_disc_taken */
1994 	to_number(''),			/* acctd_unearned_disc_taken */
1995 	to_number(''),			/* factor_discount_amount */
1996 	to_number(''),			/* acctd_factor_discount_amount */
1997 	'',  				/* interface_line_context */
1998 	'',  				/* interface_line_attribute1 */
1999 	'',  				/* interface_line_attribute2 */
2000 	'',   				/* interface_line_attribute3 */
2001 	'',  				/* interface_line_attribute4 */
2002 	'',  				/* interface_line_attribute5 */
2003 	'',   				/* interface_line_attribute6 */
2004 	'',   				/* interface_line_attribute7 */
2005 	'',   				/* interface_line_attribute8 */
2006 	'',   				/* interface_line_attribute9 */
2007 	'',   				/* interface_line_attribute10 */
2008 	'',   				/* interface_line_attribute11 */
2009 	'',   				/* interface_line_attribute12 */
2010 	'',   				/* interface_line_attribute13 */
2011 	'',   				/* interface_line_attribute14 */
2012 	'',    				/* interface_line_attribute15 */
2013 	'', 				/* exchange_rate_type */
2014 	to_date(null),			/* exchange_rate_date */
2015         to_number(''),  		/* exchange_rate */
2016 	to_date(null),			/* due_date */
2017 	to_date(null),			/* apply_date */
2018         to_number(''),			/* movement_id */
2019         '',				/* tax_vendor_return_code */
2020         '',				/* tax_authority_tax_rates */
2021         '',				/* tax_exemption_flag */
2022         to_number(''),			/* tax_exemption_id */
2023         '',				/* exemption_type */
2024         '',				/* exemption_reason */
2025         '',				/* customer_exemption_number */
2026         '',				/* item_exception_rate */
2027         '', 				/* item_exception_reason */
2028 	'',				/* original_collectibility_flag */
2029 	'',				/* line_collectible_flag */
2030 	'',				/* manual_override_flag */
2031 	lc.contingency_code,		/* contingency_code */
2032 	lc.expiration_date, 		/* expiration_date */
2033 	lc.expiration_days,		/* expiration_days */
2034 	''			/* override_auto_accounting_flag */
2035 	FROM
2036         ra_customer_trx_lines ctl,
2037         ar_line_conts lc
2038 	WHERE   cp_customer_trx_id    = ctl.customer_trx_id
2039 	and	ctl.customer_trx_line_id   = lc.customer_trx_line_id
2040         and     cp_archive_level <> 'H'
2041         UNION ALL /* Bug 5105156 - fix 5044763 */
2042         ---------------------------------------------------------------------
2043         -- REC information (CRH)
2044         -- all levels
2045         ---------------------------------------------------------------------
2046         SELECT
2047         cr.type trx_class,			/* transaction_class */
2048         '' trx_type,				/* transaction_type */
2049         cr.cash_receipt_id trx_id,		/* transaction_id */
2050         to_number('') line_id,			/* transaction_line_id */
2051         '' related_trx_class,			/* related_transaction_class */
2052         '' related_trx_type,			/* related_transaction_type */
2053         to_number('') related_trx_id,		/* related_transaction_id */
2054         to_number('') related_trx_line_id,	/* related_transaction_line_id */
2055         to_number('') line_number,  		/* line_number */
2056         'CRH' dist_type, 			/* distribution_type */
2057         '' app_type,				/* application_type */
2058         '' line_code_meaning,  		/* line_code_meaning */
2059         '' description,			/* description */
2060         '' item_name,				/* item_name */
2061         to_number('') qty,			/* quantity */
2062         to_number('') selling_price,			/* unit_selling_price */
2063         '' line_type,				/* line_type */
2064         crh.attribute_category attr_category,
2065         crh.attribute1 attr1,
2066         crh.attribute2 attr2,
2067         crh.attribute3 attr3,
2068         crh.attribute4 attr4,
2069         crh.attribute5 attr5,
2070         crh.attribute6 attr6,
2071         crh.attribute7 attr7,
2072         crh.attribute8 attr8,
2073         crh.attribute9 attr9,
2074         crh.attribute10 attr10,
2075         crh.attribute11 attr11,
2076         crh.attribute12 attr12,
2077         crh.attribute13 attr13,
2078         crh.attribute14 attr14,
2079         crh.attribute15 attr15,
2080         crh.amount amount,
2081         crh.acctd_amount acctd_amount,
2082         '' uom_code,  				/* uom code */
2083         cr.ussgl_transaction_code ussgl_trx_code,
2084         vt.tax_rate tax_rate,				/* tax_rate */
2085         vt.tax_code tax_code, 				/* tax_code */
2086         to_number('') tax_precedence,				/* tax_precedence */
2087         crh.account_code_combination_id ccid1,
2088         crh.bank_charge_account_ccid ccid2,
2089         to_number('') ccid3, 			/* account_ccid3 */
2090         to_number('') ccid4,  			/* account_ccid4 */
2091         crh.gl_date gl_date,
2092         crh.gl_posted_date gl_posted_date,
2093         '' rule_name, 				/* acct_rule_name */
2094         to_number('') acctg_rule_duration,  	/* rule_duration */
2095         to_date(NULL) rule_start_date,		/* rule_start_date */
2096         to_number('') last_period_to_credit, 	/* last_period_to_credit */
2097         '' line_comment, 			/* line_comment */
2098         to_number('') line_adjusted,		/* line_adjusted */
2099         to_number('') freight_adjusted,	/* freight_adjusted */
2100         to_number('') tax_adjusted,		/* tax_adjusted */
2101         to_number('') charges_adjusted,	/* receivables_charges_adjusted */
2102         to_number('') line_applied,		/* line_applied */
2103         to_number('') freight_applied,		/* freight_applied */
2104         to_number('') tax_applied,		/* tax_applied */
2105         to_number('') charges_adjusted,	/* receivables_charges_applied */
2106         to_number('') earned_disc_taken,	/* earned_discount_taken */
2107         to_number('') unearned_disc_taken,	/* unearned_discount_taken */
2108         to_number('') acctd_amount_applied_from,/* acctd_amount_applied_from */
2109         to_number('') acctd_amount_applied_to,	/* acctd_amount_applied_to */
2110         to_number('') acctd_earned_disc_taken,	/* acctd_earned_disc_taken */
2111         to_number('') acctd_unearned_disc_taken,/* acctd_unearned_disc_taken */
2112         crh.factor_discount_amount factor_discount_amount,
2113                 /* factor_discount_amount */
2114         crh.acctd_factor_discount_amount acctd_factor_discount_amount,
2115                 /* acctd_factor_discount_amount */
2116          '' int_line_context,    	/* interface_line_context */
2117          '' int_line_attr1,   		/* interface_line_attribute1 */
2118          '' int_line_attr2,    	/* interface_line_attribute2 */
2119          '' int_line_attr3,    	/* interface_line_attribute3 */
2120          '' int_line_attr4,   		/* interface_line_attribute4 */
2121          '' int_line_attr5,   		/* interface_line_attribute5 */
2122          '' int_line_attr6,   		/* interface_line_attribute6 */
2123          '' int_line_attr7,    	/* interface_line_attribute7 */
2124          '' int_line_attr8,   		/* interface_line_attribute8 */
2125          '' int_line_attr9,    	/* interface_line_attribute9 */
2126          '' int_line_attr10,   	/* interface_line_attribute10 */
2127          '' int_line_attr11,   	/* interface_line_attribute11 */
2128          '' int_line_attr12,   	/* interface_line_attribute12 */
2129          '' int_line_attr13,   	/* interface_line_attribute13 */
2130          '' int_line_attr14,   	/* interface_line_attribute14 */
2131          '' int_line_attr15,   		/* interface_line_attribute15 */
2132          crh.exchange_rate_type exch_rate_type,
2133          crh.exchange_date exch_date,
2134          crh.exchange_rate exch_rate,
2135          to_date(NULL) due_date,			/* due_date */
2136          to_date(NULL) apply_date,		/* apply_date */
2137          to_number('') movement_id,		/* movement_id */
2138          '' vendor_return_code,		/* tax_vendor_return_code */
2139          '' tax_auth_tax_rate,			/* tax_authority_tax_rates */
2140          '' tax_exempt_flag,			/* tax_exemption_flag */
2141          to_number('') tax_exemption_id,	/* tax_exemption_id */
2142          '' exemption_type,			/* exemption_type */
2143          '' tax_exemption_reason,		/* exemption_reason */
2144          '' tax_exemption_number,		/* customer_exemption_number */
2145          '' item_exception_rate,		/* item_exception_rate */
2146          '' meaning,                            /* item_exception_reason */
2147          '',                             /* original_collectibility_flag */
2148          '',                             /* line_collectible_flag */
2149          '',                             /* manual_override_flag */
2150          '',                             /* contingency_code */
2151          to_date(null),                  /* expiration_date */
2152          to_number(null),                /* expiration_days */
2153 	 ''			 /* override_auto_accounting_flag */
2154          FROM
2155          ar_vat_tax vt,
2156          ar_cash_receipt_history crh,
2157          ar_cash_receipts  cr ,
2158          ar_receivable_applications ra
2159          WHERE  crh.cash_receipt_id     = cr.cash_receipt_id
2160          and	nvl(crh.current_record_flag, 'N') = 'Y'
2161          and    cr.vat_tax_id = vt.vat_tax_id (+)
2162          and 	cr.cash_receipt_id     = ra.cash_receipt_id
2163          and    ra.applied_customer_trx_id = cp_customer_trx_id
2164         -- bug3567865 Don't insert duplicate cash record.
2165         and    not exists (
2166                   select 'already purged'
2167                     from ar_archive_detail aad
2168                    where aad.transaction_id = cr.cash_receipt_id
2169                      and aad.transaction_class = 'CASH' )
2170          UNION ALL /* Bug 5105156 - fix 5044763 */
2171          ---------------------------------------------------------------------
2172          -- REC_APP of
2173          -- all invoices pertaining to the receipt of the invoice
2174          ---------------------------------------------------------------------
2175          SELECT
2176          cr.type trx_class, 			/* transaction_class */
2177          '' trx_type,				/* transaction_type */
2178          cr.cash_receipt_id trx_id,		/* transaction_id */
2179          to_number('') line_id,			/* transaction_line_id */
2180          ctt.type related_trx_class,			/* related_transaction_class */
2181          ctt.name related_trx_type,			/* related_transaction_type */
2182          ct.customer_trx_id related_trx_id,		/* related_transaction_id */
2183          to_number('') related_trx_line_id,			/* related_transaction_line_id */
2184          to_number('') line_number,  			/* line_number */
2185          'REC_APP' dist_type, 			/* distribution_type */
2186          ra.application_type app_type,		/* application_type */
2187          '' line_code_meaning, 				/* line_code_meaning */
2188          '' description,				/* description */
2189          '' item_name,				/* item_name */
2190          to_number('') qty,			/* quantity */
2191          to_number('') selling_price,			/* unit_selling_price */
2192          '' line_type,				/* line_type */
2193          ra.attribute_category attr_category,
2194          ra.attribute1 attr1,
2195          ra.attribute2 attr2,
2196          ra.attribute3 attr3,
2197          ra.attribute4 attr4,
2198          ra.attribute5 attr5,
2199          ra.attribute6 attr6,
2200          ra.attribute7 attr7,
2201          ra.attribute8 attr8,
2202          ra.attribute9 attr9,
2203          ra.attribute10 attr10,
2204          ra.attribute11 attr11,
2205          ra.attribute12 attr12,
2206          ra.attribute13 attr13,
2207          ra.attribute14 attr14,
2208          ra.attribute15 attr15,
2209          ra.amount_applied amount, /* amount */
2210          to_number('') acctd_amount,			/* acctd_amount */
2211          '' uom_code,  					/* uom code */
2212          cr.ussgl_transaction_code ussgl_trx_code,
2213          to_number('') tax_rate,		/* tax_rate */
2214          '' tax_code, 				/* tax_code */
2215          to_number('') tax_precedence,			/* tax_precedence */
2216          ra.code_combination_id ccid1,    /* account_ccid1 */
2217          to_number('') ccid2, 		   /* account_ccid2 */
2218          ra.earned_discount_ccid ccid3,   /* account_ccid3 */
2219          ra.unearned_discount_ccid ccid4, /* account_ccid4 */
2220          ra.gl_date gl_date,
2221          ra.gl_posted_date gl_posted_date,
2222          '' rule_name, 		    /* acct_rule_name */
2223          to_number('') acctg_rule_duration,/* rule_duration */
2224          to_date(NULL) rule_start_date,	    /* rule_start_date */
2225          to_number('') last_period_to_credit,  /* last_period_to_credit */
2226          ra.comments line_comment, 		/* line_comment */
2227          to_number('') line_adjusted,	        /* line_adjusted */
2228          to_number('') freight_adjusted,	/* freight_adjusted */
2229          to_number('') tax_adjusted,		/* tax_adjusted */
2230          to_number('') charges_adjusted,	/* receivables_charges_adjusted */
2231          ra.line_applied line_applied,		/* line_applied */
2232          ra.freight_applied freight_applied,	/* freight_applied */
2233          ra.tax_applied tax_applied,		/* tax_applied */
2234          ra.receivables_charges_applied charges_applied,/* receivables_charges_applied */
2235          ra.earned_discount_taken earned_disc_taken,	 /* earned_discount_taken */
2236          ra.unearned_discount_taken unearned_disc_taken,/* unearned_discount_taken */
2237          ra.acctd_amount_applied_from acctd_amount_applied_from,
2238                 /* acctd_amount_applied_from */
2239          ra.acctd_amount_applied_to acctd_amount_applied_to,
2240                 /* acctd_amount_applied_to */
2241          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
2242                 /* acctd_earned_disc_taken */
2243          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
2244                 /* acctd_unearned_disc_taken */
2245          to_number('') factor_discount_amount,	/* factor_discount_amount */
2246          to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
2247          '' int_line_context,    		/* interface_line_context */
2248          '' int_line_attr1,   			/* interface_line_attribute1 */
2249          '' int_line_attr2,  			/* interface_line_attribute2 */
2250          '' int_line_attr3,   			/* interface_line_attribute3 */
2251          '' int_line_attr4,   			/* interface_line_attribute4 */
2252          '' int_line_attr5,   			/* interface_line_attribute5 */
2253          '' int_line_attr6,   			/* interface_line_attribute6 */
2254          '' int_line_attr7,   			/* interface_line_attribute7 */
2255          '' int_line_attr8,   			/* interface_line_attribute8 */
2256          '' int_line_attr9,   			/* interface_line_attribute9 */
2257          '' int_line_attr10,   		/* interface_line_attribute10 */
2258          '' int_line_attr11,   		/* interface_line_attribute11 */
2259          '' int_line_attr12,  			/* interface_line_attribute12 */
2260          '' int_line_attr13,  			/* interface_line_attribute13 */
2261          '' int_line_attr14,  			/* interface_line_attribute14 */
2262          '' int_line_attr15,    		/* interface_line_attribute15 */
2263          '' exch_rate_type,			/* exchange_rate_type */
2264          to_date(NULL) exch_date,  		/* exchange_date */
2265          to_number('') exch_rate,		/* exchange_rate */
2266          ps.due_date due_date,
2267          ra.apply_date apply_date,
2268          to_number('') movement_id,		/* movement_id */
2269          '' vendor_return_code,		/* tax_vendor_return_code */
2270          '' tax_auth_tax_rate,			/* tax_authority_tax_rates */
2271          '' tax_exempt_flag,			/* tax_exemption_flag */
2272          to_number('') tax_exemption_id,	/* tax_exemption_id */
2273          '' exemption_type,			/* exemption_type */
2274          '' tax_exemption_reason,              /* exemption_reason */
2275          '' tax_exemption_number,		/* customer_exemption_number */
2276          '' item_exception_rate,		/* item_exception_rate */
2277          '' meaning,		                /* item_exception_reason */
2278          '',                             /* original_collectibility_flag */
2279          '',                             /* line_collectible_flag */
2280          '',                             /* manual_override_flag */
2281          '',                             /* contingency_code */
2282          to_date(null),                  /* expiration_date */
2283          to_number(null),                /* expiration_days */
2284 	 ''			 /* override_auto_accounting_flag */
2285          FROM
2286          ra_cust_trx_types ctt,
2287          ar_payment_schedules ps,
2288          ar_cash_receipts  cr,
2289          ar_receivable_applications ra,
2290          ra_customer_trx   ct
2291          WHERE   ctt.cust_trx_type_id    = ct.cust_trx_type_id
2292          and 	ps.payment_schedule_id (+) = ra.applied_payment_schedule_id
2293          and 	cr.cash_receipt_id     = ra.cash_receipt_id
2294          and 	ra.applied_customer_trx_id = ct.customer_trx_id
2295          and    exists ( SELECT 'x'
2296                          FROM   ar_receivable_applications ra1
2297                          WHERE  ra1.applied_customer_trx_id = cp_customer_trx_id
2298                          AND    ra1.cash_Receipt_id = ra.cash_receipt_id )
2299         -- bug3567865 Don't insert duplicate cash record.
2300         and    not exists (
2301                   select 'already purged'
2302                     from ar_archive_detail aad
2303                    where aad.transaction_id = cr.cash_receipt_id
2304                      and aad.transaction_class = 'CASH' )
2305          UNION ALL /* Bug 5105156 - fix 5044763 */
2306          ---------------------------------------------------------------------
2307          -- CM applications (CM_APP)
2308          -- all levels
2309          ---------------------------------------------------------------------
2310          SELECT
2311          ctt_cm.type trx_class,		/* transaction_class */
2312          ctt_cm.name trx_type,			/* transaction_type */
2313          ct_cm.customer_trx_id trx_id, 	/* transaction_id */
2314          to_number('') line_id,		/* transaction_line_id */
2315          ctt_inv.type related_trx_class,	/* related_transaction_class */
2316          ctt_inv.name related_trx_type,	/* related_transaction_type */
2317          ct_inv.customer_trx_id related_trx_id,/* related_transaction_id */
2318          to_number('') related_trx_line_id,	/* related_transaction_line_id */
2319          to_number('') line_number,		/* line_number */
2320          'CM_APP' dist_type, 			/* distribution_type */
2321          ra.application_type app_type,		/* application_type */
2322          '' line_code_meaning, 		/* line_code_meaning */
2323          '' description,
2324          '' item_name,			/* item_name */
2325          to_number('') qty,		/* quantity */
2326          to_number('') selling_price,	/* unit_selling_price */
2327          '' line_type,
2328          ra.attribute_category attr_category,
2329          ra.attribute1 attr1,
2330          ra.attribute2 attr2,
2331          ra.attribute3 attr3,
2332          ra.attribute4 attr4,
2333          ra.attribute5 attr5,
2334          ra.attribute6 attr6,
2335          ra.attribute7 attr7,
2336          ra.attribute8 attr8,
2337          ra.attribute9 attr9,
2338          ra.attribute10 attr10,
2339          ra.attribute11 attr11,
2340          ra.attribute12 attr12,
2341          ra.attribute13 attr13,
2342          ra.attribute14 attr14,
2343          ra.attribute15 attr15,
2344          ra.amount_applied,		/* amount */
2345          to_number('') acctd_amount,		/* acctd_amount */
2346          '' uom_code,
2347          '' ussgl_trx_code,
2348          to_number('') tax_rate,			/* tax_rate */
2349          '' tax_code,				/* tax_code */
2350          to_number('') tax_precedence,			/* tax_precedence */
2351          ra.code_combination_id ccid1,    /* account_ccid1 */
2352          to_number('') ccid2, 		   /* account_ccid2 */
2353          ra.unearned_discount_ccid ccid3, /* account_ccid3 */
2354          ra.earned_discount_ccid ccid4,
2355          ra.gl_date gl_date,
2356          ra.gl_posted_date gl_posted_date,
2357          '' rule_name, 		        /* acct_rule_name */
2358          to_number('') acctg_rule_duration,	/* rule_duration */
2359          to_date(NULL) rule_start_date,		/* rule_start_date */
2360          to_number('') last_period_to_credit, 	/* last_period_to_credit */
2361          ra.comments line_comment, 		/* line_comment */
2362          to_number('') line_adjusted,		/* line_adjusted */
2363          to_number('') freight_adjusted,	/* freight_adjusted */
2364          to_number('') tax_adjusted,		/* tax_adjusted */
2365          to_number('') charges_adjusted,	/* receivables_charges_adjusted */
2366          ra.line_applied line_applied,		/* line_applied */
2367          ra.freight_applied freight_applied,	/* freight_applied */
2368          ra.tax_applied tax_applied,		/* tax_applied */
2369          ra.receivables_charges_applied charges_applied,    /* receivables_charges_applied */
2370          ra.earned_discount_taken earned_disc_taken,	     /* earned_discount_taken */
2371          ra.unearned_discount_taken unearned_disc_taken,    /* unearned_discount_taken */
2372          ra.acctd_amount_applied_from acctd_amount_applied_from,
2373                 /* acctd_amount_applied_from */
2374          ra.acctd_amount_applied_to acctd_amount_applied_to,
2375                 /* acctd_amount_applied_to */
2376          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
2377                 /* acctd_earned_disc_taken */
2378          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
2379                 /* acctd_unearned_disc_taken */
2380          to_number('') factor_discount_amount,		/* factor_discount_amount */
2381          to_number('') acctd_factor_discount_amount,	/* acctd_factor_discount_amount */
2382          '' int_line_context,		/* interface_line_context */
2383          '' int_line_attr1,				/* interface_line_attribute1 */
2384          '' int_line_attr2,				/* interface_line_attribute2 */
2385          '' int_line_attr3,				/* interface_line_attribute3 */
2386          '' int_line_attr4,				/* interface_line_attribute4 */
2387          '' int_line_attr5,				/* interface_line_attribute5 */
2388          '' int_line_attr6,				/* interface_line_attribute6 */
2389          '' int_line_attr7,				/* interface_line_attribute7 */
2390          '' int_line_attr8,				/* interface_line_attribute8 */
2391          '' int_line_attr9,				/* interface_line_attribute9 */
2392          '' int_line_attr10,				/* interface_line_attribute10 */
2393          '' int_line_attr11,				/* interface_line_attribute11 */
2394          '' int_line_attr12,				/* interface_line_attribute12 */
2395          '' int_line_attr13,				/* interface_line_attribute13 */
2396          '' int_line_attr14,				/* interface_line_attribute14 */
2397          '' int_line_attr15,				/* interface_line_attribute15 */
2398          '' exch_rate_type, 				/* exchange_rate_type */
2399          to_date(NULL) exch_date,			/* exchange_rate_date */
2400          to_number('') exch_rate,		/* exchange_rate */
2401          to_date(NULL) due_date, 		/* due_date */
2402          ra.apply_date apply_date,
2403          to_number('') movement_id,		/* movement_id */
2404          '' vendor_return_code, 		/* tax_vendor_return_code */
2405          '' tax_auth_tax_rate,			/* tax_authority_tax_rates */
2406          '' tax_exempt_flag,			/* tax_exemption_flag */
2407          to_number('') tax_exemption_id,	/* tax_exemption_id */
2408          '' exemption_type, 			/* exemption_type */
2409          '' tax_exemption_reason,		/* reason_code */
2410          '' tax_exemption_number,		/* customer_exemption_number */
2411          '' item_exception_rate, 		/* item_exception_rate */
2412          '' meaning ,				/* item_exception_reason */
2413          '',                             /* original_collectibility_flag */
2414          '',                             /* line_collectible_flag */
2415          '',                             /* manual_override_flag */
2416          '',                             /* contingency_code */
2417          to_date(null),                  /* expiration_date */
2418          to_number(null),                /* expiration_days */
2419 	 ''			 /* override_auto_accounting_flag */
2420          FROM
2421          ra_cust_trx_types ctt_cm,
2422          ra_customer_trx   ct_cm,
2423          ra_cust_trx_types ctt_inv,
2424          ar_receivable_applications ra,
2425          ra_customer_trx   ct_inv
2426          WHERE ctt_cm.cust_trx_type_id = ct_cm.cust_trx_type_id
2427          AND   ra.applied_customer_trx_id = ct_inv.customer_trx_id
2428          AND   ra.customer_trx_id = ct_cm.customer_trx_id
2429          -- bug3948805 removed
2430          -- AND   ct_cm.previous_customer_trx_id = ct_inv.customer_trx_id
2431          AND   ctt_inv.cust_trx_type_id = ct_inv.cust_trx_type_id
2432          AND   ctt_inv.type <> 'CM'
2433          -- bug3948805 added condition for ct_cm.customer_trx_id
2434          AND   ( ct_inv.customer_trx_id = cp_customer_trx_id
2435                  or   ct_cm.customer_trx_id = cp_customer_trx_id )
2436 
2437          UNION ALL /* Bug 5105156 - fix 5073245 starts */
2438          ---------------------------------------------------------------------
2439          -- REC_WRITE_OFFs
2440          -- all write-offs pertaining to receipts of the invoices
2441          ---------------------------------------------------------------------
2442          SELECT
2443          cr.type trx_class,                     /* transaction_class */
2444          '' trx_type,                           /* transaction_type */
2445          cr.cash_receipt_id trx_id,             /* transaction_id */
2446          to_number('') line_id,                 /* transaction_line_id */
2447          'Activity' related_trx_class,                    /* related_transaction_class */
2448          'Write_Off' related_trx_type,                     /* related_transaction_type */
2449          to_number('') related_trx_id,             /* related_transaction_id */
2450          to_number('') related_trx_line_id,                     /* related_transaction_line_id */
2451          to_number('') line_number,                     /* line_number */
2452          'REC_APP' dist_type,                   /* distribution_type */
2453          ra.application_type app_type,          /* application_type */
2454          '' line_code_meaning,                          /* line_code_meaning */
2455          '' description,                                /* description */
2456          '' item_name,                          /* item_name */
2457          to_number('') qty,                     /* quantity */
2458          to_number('') selling_price,                   /* unit_selling_price */
2459          '' line_type,                          /* line_type */
2460          ra.attribute_category attr_category,
2461          ra.attribute1 attr1,
2462          ra.attribute2 attr2,
2463          ra.attribute3 attr3,
2464          ra.attribute4 attr4,
2465          ra.attribute5 attr5,
2466          ra.attribute6 attr6,
2467          ra.attribute7 attr7,
2468          ra.attribute8 attr8,
2469          ra.attribute9 attr9,
2470          ra.attribute10 attr10,
2471          ra.attribute11 attr11,
2472          ra.attribute12 attr12,
2473          ra.attribute13 attr13,
2474          ra.attribute14 attr14,
2475          ra.attribute15 attr15,
2476          ra.amount_applied amount, /* amount */
2477          to_number('') acctd_amount,                    /* acctd_amount */
2478          '' uom_code,                                   /* uom code */
2479          cr.ussgl_transaction_code ussgl_trx_code,
2480          to_number('') tax_rate,                /* tax_rate */
2481          '' tax_code,                           /* tax_code */
2482          to_number('') tax_precedence,                  /* tax_precedence */
2483          ra.code_combination_id ccid1,    /* account_ccid1 */
2484          to_number('') ccid2,              /* account_ccid2 */
2485          ra.earned_discount_ccid ccid3,   /* account_ccid3 */
2486          ra.unearned_discount_ccid ccid4, /* account_ccid4 */
2487          ra.gl_date gl_date,
2488          ra.gl_posted_date gl_posted_date,
2489          '' rule_name,              /* acct_rule_name */
2490          to_number('') acctg_rule_duration,/* rule_duration */
2491          to_date(NULL) rule_start_date,     /* rule_start_date */
2492          to_number('') last_period_to_credit,  /* last_period_to_credit */
2493          ra.comments line_comment,              /* line_comment */
2494          to_number('') line_adjusted,           /* line_adjusted */
2495          to_number('') freight_adjusted,        /* freight_adjusted */
2496          to_number('') tax_adjusted,            /* tax_adjusted */
2497          to_number('') charges_adjusted,        /* receivables_charges_adjusted */
2498          ra.line_applied line_applied,          /* line_applied */
2499          ra.freight_applied freight_applied,    /* freight_applied */
2500          ra.tax_applied tax_applied,            /* tax_applied */
2501          ra.receivables_charges_applied charges_applied,/* receivables_charges_applied */
2502          ra.earned_discount_taken earned_disc_taken,     /* earned_discount_taken */
2503          ra.unearned_discount_taken unearned_disc_taken,/* unearned_discount_taken */
2504          ra.acctd_amount_applied_from acctd_amount_applied_from,
2505                 /* acctd_amount_applied_from */
2506          ra.acctd_amount_applied_to acctd_amount_applied_to,
2507                 /* acctd_amount_applied_to */
2508          ra.acctd_earned_discount_taken acctd_earned_disc_taken,
2509                 /* acctd_earned_disc_taken */
2510          ra.acctd_unearned_discount_taken acctd_unearned_disc_taken,
2511                 /* acctd_unearned_disc_taken */
2512          to_number('') factor_discount_amount,  /* factor_discount_amount */
2513          to_number('') acctd_factor_discount_amount,/* acctd_factor_discount_amount */
2514          '' int_line_context,                   /* interface_line_context */
2515          '' int_line_attr1,                     /* interface_line_attribute1 */
2516          '' int_line_attr2,                     /* interface_line_attribute2 */
2517          '' int_line_attr3,                     /* interface_line_attribute3 */
2518          '' int_line_attr4,                     /* interface_line_attribute4 */
2519          '' int_line_attr5,                     /* interface_line_attribute5 */
2520          '' int_line_attr6,                     /* interface_line_attribute6 */
2521          '' int_line_attr7,                     /* interface_line_attribute7 */
2522          '' int_line_attr8,                     /* interface_line_attribute8 */
2523          '' int_line_attr9,                     /* interface_line_attribute9 */
2524          '' int_line_attr10,            /* interface_line_attribute10 */
2525          '' int_line_attr11,            /* interface_line_attribute11 */
2526          '' int_line_attr12,                    /* interface_line_attribute12 */
2527          '' int_line_attr13,                    /* interface_line_attribute13 */
2528          '' int_line_attr14,                    /* interface_line_attribute14 */
2529          '' int_line_attr15,                    /* interface_line_attribute15 */
2530          '' exch_rate_type,                     /* exchange_rate_type */
2531          to_date(NULL) exch_date,               /* exchange_date */
2532          to_number('') exch_rate,               /* exchange_rate */
2533          to_date(NULL) due_date,
2534          ra.apply_date apply_date,
2535          to_number('') movement_id,             /* movement_id */
2536          '' vendor_return_code,         /* tax_vendor_return_code */
2537          '' tax_auth_tax_rate,                  /* tax_authority_tax_rates */
2538          '' tax_exempt_flag,                    /* tax_exemption_flag */
2539          to_number('') tax_exemption_id,        /* tax_exemption_id */
2540          '' exemption_type,                     /* exemption_type */
2541          '' tax_exemption_reason,              /* exemption_reason */
2542          '' tax_exemption_number,               /* customer_exemption_number */
2543          '' item_exception_rate,                /* item_exception_rate */
2544          '' meaning,                            /* item_exception_reason */
2545          '',                             /* original_collectibility_flag */
2546          '',                             /* line_collectible_flag */
2547          '',                             /* manual_override_flag */
2548          '',                             /* contingency_code */
2549          to_date(null),                  /* expiration_date */
2550          to_number(null),                /* expiration_days */
2551          ''                      /* override_auto_accounting_flag */
2552          FROM
2553          ar_cash_receipts  cr,
2554          ar_receivable_applications ra
2555          where  cr.cash_receipt_id     = ra.cash_receipt_id
2556          and    ra.applied_payment_schedule_id = -3
2557          and    ra.status = 'ACTIVITY'
2558          and    ra.display = 'Y'
2559          and    ra.reversal_gl_date is null
2560          and    exists ( SELECT 'x'
2561                          FROM   ar_receivable_applications ra1
2562                          WHERE  ra1.applied_customer_trx_id =
2563                                      cp_customer_trx_id
2564                          AND    ra1.cash_Receipt_id = ra.cash_receipt_id )
2565          and    not exists (
2566                   select 'already purged'
2567                     from ar_archive_detail aad
2568                    where aad.transaction_id = cr.cash_receipt_id
2569                      and aad.transaction_class = 'CASH' );
2570 
2571          /* Bug 5105156 - fix 5073245 ends */
2572 
2573 
2574          l_org_profile VARCHAR2(30) ;
2575 
2576          l_account_combination1 VARCHAR2(240) ;
2577          l_account_combination2 VARCHAR2(240) ;
2578          l_account_combination3 VARCHAR2(240) ;
2579          l_account_combination4 VARCHAR2(240) ;
2580 
2581      BEGIN
2582 
2583 
2584          oe_profile.get('SO_ORGANIZATION_ID', l_org_profile);
2585 
2586          FOR select_detail IN detail_cursor ( p_customer_trx_id,
2587                                               p_archive_level ,
2588                                               l_org_profile )
2589          LOOP
2590 
2591              l_account_combination1 := NULL ;
2592              l_account_combination2 := NULL ;
2593              l_account_combination3 := NULL ;
2594              l_account_combination4 := NULL ;
2595              --
2596              IF select_detail.ccid1 > 0 THEN
2597                 l_account_combination1 := get_ccid(select_detail.ccid1) ;
2598              END IF ;
2599              --
2600              IF select_detail.ccid2 > 0 THEN
2601                 l_account_combination2 := get_ccid(select_detail.ccid2) ;
2602              END IF ;
2603              --
2604              IF select_detail.ccid3 > 0 THEN
2605                 l_account_combination3 := get_ccid(select_detail.ccid3) ;
2606              END IF ;
2607              --
2608              IF select_detail.ccid4 > 0 THEN
2609                 l_account_combination4 := get_ccid(select_detail.ccid4) ;
2610              END IF ;
2611              --
2612              INSERT INTO ar_archive_detail
2613              ( archive_id,
2614                transaction_class,
2615                transaction_type,
2616                transaction_id,
2617                transaction_line_id,
2618                related_transaction_class,
2619                related_transaction_type,
2620                related_transaction_id,
2621                related_transaction_line_id,
2622                line_number,
2623                distribution_type,
2624                application_type,
2625                reason_code_meaning,
2626                line_description,
2627                item_name,
2628                quantity,
2629                unit_selling_price,
2630                line_type,
2631                attribute_category,
2632                attribute1,
2633                attribute2,
2634                attribute3,
2635                attribute4,
2636                attribute5,
2637                attribute6,
2638                attribute7,
2639                attribute8,
2640                attribute9,
2641                attribute10,
2642                attribute11,
2643                attribute12,
2644                attribute13,
2645                attribute14,
2646                attribute15,
2647                amount,
2648                -- acctd_amount, -- bug1199027
2649                uom_code,
2650                ussgl_transaction_code,
2651                tax_rate,
2652                tax_code,
2653                tax_precedence,
2654                account_combination1,
2655                account_combination2,
2656                account_combination3,
2657                account_combination4,
2658                gl_date,
2659                gl_posted_date,
2660                accounting_rule_name,
2661                rule_duration,
2662                rule_start_date,
2663                last_period_to_credit,
2664                comments,
2665                line_adjusted,
2666                freight_adjusted,
2667                tax_adjusted,
2668                receivables_charges_adjusted,
2669                line_applied,
2670                freight_applied,
2671                tax_applied,
2672                receivables_charges_applied,
2673                earned_discount_taken,
2674                unearned_discount_taken,
2675                -- acctd_amount_applied_from, -- bug1199027
2676                -- acctd_amount_applied_to, -- bug1199027
2677                -- acctd_earned_disc_taken, -- bug1199027
2678                -- acctd_unearned_disc_taken, -- bug1199027
2679                factor_discount_amount,
2680                -- acctd_factor_discount_amount, -- bug1199027
2681                interface_line_context,
2682                interface_line_attribute1,
2683                interface_line_attribute2,
2684                interface_line_attribute3,
2685                interface_line_attribute4,
2686                interface_line_attribute5,
2687                interface_line_attribute6,
2688                interface_line_attribute7,
2689                interface_line_attribute8,
2690                interface_line_attribute9,
2691                interface_line_attribute10,
2692                interface_line_attribute11,
2693                interface_line_attribute12,
2694                interface_line_attribute13,
2695                interface_line_attribute14,
2696                interface_line_attribute15,
2697                exchange_rate_type,
2698                exchange_rate_date,
2699                exchange_rate,
2700                due_date,
2701                apply_date,
2702                movement_id,
2703                tax_vendor_return_code,
2704                tax_authority_tax_rates,
2705                tax_exemption_flag,
2706                tax_exemption_id,
2707                tax_exemption_type,
2708                tax_exemption_reason,
2709                tax_exemption_number,
2710                item_exception_rate,
2711                Item_exception_reason ,
2712                original_collectibility_flag,
2713                line_collectible_flag,
2714                manual_override_flag,
2715                contingency_code,
2716                expiration_date,
2717                expiration_days,
2718 	       override_auto_accounting_flag
2719              )
2720              VALUES
2721              ( lpad(p_archive_id,14,'0'), /* modified for bug 3266428 */
2722                select_detail.trx_class,
2723                select_detail.trx_type,
2724                select_detail.trx_id,
2725                select_detail.line_id,
2726                select_detail.related_trx_class,
2727                select_detail.related_trx_type,
2728                select_detail.related_trx_id,
2729                select_detail.related_trx_line_id,
2730                select_detail.line_number,
2731                select_detail.dist_type,
2732                select_detail.app_type,
2733                select_detail.line_code_meaning,
2734                select_detail.description,
2735                select_detail.item_name,
2736                select_detail.qty,
2737                select_detail.selling_price,
2738                select_detail.line_type,
2739                select_detail.attr_category,
2740                select_detail.attr1,
2741                select_detail.attr2,
2742                select_detail.attr3,
2743                select_detail.attr4,
2744                select_detail.attr5,
2745                select_detail.attr6,
2746                select_detail.attr7,
2747                select_detail.attr8,
2748                select_detail.attr9,
2749                select_detail.attr10,
2750                select_detail.attr11,
2751                select_detail.attr12,
2752                select_detail.attr13,
2753                select_detail.attr14,
2754                select_detail.attr15,
2755                select_detail.amount,
2756                -- select_detail.acctd_amount, -- bug1199027
2757                select_detail.uom_code,
2758                select_detail.ussgl_trx_code,
2759                select_detail.tax_rate,
2760                select_detail.tax_code,
2761                select_detail.tax_precedence,
2762                l_account_combination1,
2763                l_account_combination2,
2764                l_account_combination3,
2765                l_account_combination4,
2766                select_detail.gl_date,
2767                select_detail.gl_posted_date,
2768                select_detail.rule_name,
2769                select_detail.acctg_rule_duration,
2770                select_detail.rule_start_date,
2771                select_detail.last_period_to_credit,
2772                select_detail.line_comment,
2773                select_detail.line_adjusted,
2774                select_detail.freight_adjusted,
2775                select_detail.tax_adjusted,
2776                select_detail.charges_adjusted,
2777                select_detail.line_applied,
2778                select_detail.freight_applied,
2779                select_detail.tax_applied,
2780                select_detail.charges_applied,
2781                select_detail.earned_disc_taken,
2782                select_detail.unearned_disc_taken,
2783                -- select_detail.acctd_amount_applied_from, -- bug1199027
2784                -- select_detail.acctd_amount_applied_to, -- bug1199027
2785                -- select_detail.acctd_earned_disc_taken, -- bug1199027
2786                -- select_detail.acctd_unearned_disc_taken, -- bug1199027
2787                select_detail.factor_discount_amount,
2788                -- select_detail.acctd_factor_discount_amount, -- bug1199027
2789                select_detail.int_line_context,
2790                select_detail.int_line_attr1,
2791                select_detail.int_line_attr2,
2792                select_detail.int_line_attr3,
2793                select_detail.int_line_attr4,
2794                select_detail.int_line_attr5,
2795                select_detail.int_line_attr6,
2796                select_detail.int_line_attr7,
2797                select_detail.int_line_attr8,
2798                select_detail.int_line_attr9,
2799                select_detail.int_line_attr10,
2800                select_detail.int_line_attr11,
2801                select_detail.int_line_attr12,
2802                select_detail.int_line_attr13,
2803                select_detail.int_line_attr14,
2804                select_detail.int_line_attr15,
2805                select_detail.exch_rate_type,
2806                select_detail.exch_date,
2807                select_detail.exch_rate,
2808                select_detail.due_date,
2809                select_detail.apply_date,
2810                select_detail.movement_id,
2811                select_detail.vendor_return_code,
2812                select_detail.tax_auth_tax_rate,
2813                select_detail.tax_exempt_flag,
2814                select_detail.tax_exemption_id,
2815                select_detail.exemption_type,
2816                select_detail.tax_exemption_reason,
2817                select_detail.tax_exemption_number,
2818                select_detail.item_exception_rate,
2819                select_detail.meaning,
2820                select_detail.original_collectibility_flag,
2821                select_detail.line_collectible_flag,
2822                select_detail.manual_override_flag,
2823                select_detail.contingency_code,
2824                select_detail.expiration_date,
2825                select_detail.expiration_days,
2826 	       select_detail.override_auto_accounting_flag
2827              ) ;
2828 
2829          END LOOP ;
2830 
2831          RETURN TRUE ;
2832 
2833     EXCEPTION
2834         WHEN OTHERS THEN
2835             print( 1, '  ...Failed while inserting into AR_ARCHIVE_DETAIL');
2836             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
2837             RAISE ;
2838     END;
2839     --
2840     -- archive - Processing Cycle
2841     --
2842     PROCEDURE archive( p_archive_id IN NUMBER,
2843                        p_customer_trx_id IN NUMBER,
2844                        p_archive_level IN VARCHAR2,
2845                        p_archive_status OUT NOCOPY BOOLEAN  ) IS
2846         l_error_location VARCHAR2(50) ;
2847         h boolean ;
2848     BEGIN
2849 
2850         -- bug3975105 add 'N'
2851         print( 1, '...archiving ', 'N');
2852         l_error_location := 'archive_header' ;
2853 
2854         IF archive_header( p_customer_trx_id ,
2855                            p_archive_id      ) = FALSE
2856         THEN
2857             print( 0, '  ...Failed while inserting into AR_ARCHIVE_HEADER ');
2858             p_archive_status := FALSE ;
2859         END IF ;
2860 
2861         l_error_location := 'archive_detail' ;
2862         IF  archive_detail( p_customer_trx_id  ,
2863                             p_archive_level    ,
2864                             p_archive_id       ) = FALSE
2865         THEN
2866             print( 0, '  ...Failed while inserting into AR_ARCHIVE_DETAIL ');
2867             p_archive_status := FALSE ;
2868         ELSE
2869             p_archive_status := TRUE ;
2870         END IF ;
2871 
2872     EXCEPTION
2873         WHEN OTHERS THEN
2874             print( 0, l_error_location ) ;
2875             print( 0, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
2876             print( 0, '  ...Archive Failed ');
2877             p_archive_status := FALSE ;
2878             RAISE ;
2879     END;
2880     --
2881     --
2882     -- returns TRUE if the entity was successfully purged
2883     -- returns FALSE otherwise
2884     --
2885     FUNCTION recursive_purge( p_entity_id       IN     NUMBER,
2886                               p_entity_type     IN     VARCHAR2,
2887                               p_as_of_gl_date   IN     DATE,
2888                               p_customer_id     IN     NUMBER,
2889                               p_archive_level   IN     VARCHAR2,
2890                               p_recursive_level IN     NUMBER,
2891                               p_running_total   IN OUT NOCOPY NUMBER ) RETURN BOOLEAN
2892     IS
2893         l_dummy          NUMBER;
2894         l_archive_status BOOLEAN ;
2895 
2896     BEGIN
2897         -- bug3975105 added 'Y'
2898         print( p_recursive_level, 'Processing id:'||p_entity_id||' type:'||p_entity_type|| ' at ' || to_char(sysdate,'dd-mon-yyyy hh:mi:ss'), 'Y');
2899 
2900         IF p_entity_type = 'CT'
2901         THEN
2902             IF in_unpurgeable_txn_list( p_entity_id )
2903             THEN
2904                 -- bug3975105 added 'S'
2905                 print( p_recursive_level, '  ...already in unpurgeable transaction list', 'S');
2906                 RETURN FALSE;
2907             END IF;
2908             --
2909             IF trx_purgeable ( p_entity_id ) = FALSE
2910             THEN
2911                 print( p_recursive_level, '  ...is unpurgeable due to customisation' ) ;
2912                 RETURN FALSE;
2913             END IF ;
2914             --
2915             DECLARE
2916                 l_record_found  VARCHAR2(10) := 'Not Found' ;
2917 
2918                 /* bug1999155: Divided select stmt which lock all transactions
2919                   records into the following stmts */
2920                 cursor trx_cur is
2921                     SELECT  'Found'  record_found
2922                     from    ra_customer_trx trx
2923                     WHERE   trx.customer_trx_id = p_entity_id
2924                     FOR     UPDATE OF trx.customer_trx_id NOWAIT;
2925 
2926                 cursor trx_line_cur is
2927                     SELECT  'Found'  record_found
2928                     from    ra_customer_trx_lines lines
2929                     WHERE   lines.customer_trx_id = p_entity_id
2930                     FOR     UPDATE OF lines.customer_trx_id NOWAIT;
2931 
2932                 cursor dist_cur is
2933                     SELECT  'Found'  record_found
2934                     from    ra_cust_trx_line_gl_dist dist
2935                     WHERE   dist.customer_trx_id = p_entity_id
2936                     FOR     UPDATE OF dist.customer_trx_id NOWAIT;
2937 
2938                 cursor sales_cur is
2939                     SELECT  'Found'  record_found
2940                     from    ra_cust_trx_line_salesreps sales
2941                     WHERE   sales.customer_trx_id = p_entity_id
2942                     FOR     UPDATE OF sales.customer_trx_id NOWAIT;
2943 
2944                 cursor adj_cur is
2945                     SELECT  'Found'  record_found
2946                     from    ar_adjustments adj
2947                     WHERE   adj.customer_trx_id  = p_entity_id
2948                     FOR     UPDATE OF adj.customer_trx_id NOWAIT;
2949 
2950                 cursor recv_app_cur is
2951                     SELECT  'Found'  record_found
2952                     from    ar_receivable_applications ra
2953                     WHERE   ra.applied_customer_trx_id = p_entity_id
2954                     FOR     UPDATE OF ra.customer_trx_id NOWAIT;
2955 
2956                 cursor pay_sched_cur is
2957                     SELECT  'Found'  record_found
2958                     from    ar_payment_schedules ps
2959                     WHERE   ps.customer_trx_id = p_entity_id
2960                     FOR     UPDATE OF ps.customer_trx_id NOWAIT;
2961 
2962             BEGIN
2963                 -- lock all the transaction records
2964                 /* bug1999155: Divided the following select stmt into
2965                   some stmts. This cursor for loop is not used .
2966                 FOR lock_rec IN (
2967                                   SELECT 'Found'  record_found
2968                                   FROM   ra_cust_trx_line_salesreps sales,
2969                                          ar_receivable_applications ra,
2970                                          ar_payment_schedules ps,
2971                                          ar_adjustments adj,
2972                                          ra_cust_trx_line_gl_dist dist,
2973                                          ra_customer_trx_lines lines,
2974                                          ra_customer_trx trx
2975                                   WHERE  trx.customer_trx_id = p_entity_id
2976                                   AND    trx.customer_trx_id = lines.customer_trx_id
2977                                   AND    trx.customer_trx_id = dist.customer_trx_id (+)
2978                                   AND    trx.customer_trx_id = sales.customer_trx_id (+)
2979                                   AND    trx.customer_trx_id = adj.customer_trx_id (+)
2980                                   AND    trx.customer_trx_id = ra.applied_customer_trx_id (+)
2981                                   AND    trx.customer_trx_id = ps.customer_trx_id (+)
2982                                   FOR    UPDATE OF trx.customer_trx_id ,
2983                                                    lines.customer_trx_id,
2984                                                    dist.customer_trx_id,
2985                                                    sales.customer_trx_id,
2986                                                    adj.customer_trx_id,
2987                                                    ra.customer_trx_id,
2988                                                    ps.customer_trx_id NOWAIT
2989                                )
2990                 LOOP
2991                     l_record_found := lock_rec.record_found ;
2992                 END LOOP ;
2993                 bug1999155 end */
2994 
2995                 /* bug1999155 : Open created cursors to lock */
2996                 open    trx_cur;
2997 
2998                 fetch  trx_cur
2999                 into l_record_found;
3000 
3001                 -- Need to verify if NO_DATA_FOUND will be raised if
3002                 -- the cursor does not return any row.
3003                 --
3004                 IF l_record_found = 'Not Found'
3005                 THEN
3006                    RETURN TRUE ; -- No Data Found
3007                 END IF ;
3008 
3009                 close   trx_cur;
3010 
3011                 open    trx_line_cur;
3012                 close   trx_line_cur;
3013 
3014                 open    dist_cur;
3015                 close   dist_cur;
3016 
3017                 open    sales_cur;
3018                 close   sales_cur;
3019 
3020                 open    adj_cur;
3021                 close   adj_cur;
3022 
3023                 open    recv_app_cur;
3024                 close   recv_app_cur;
3025 
3026                 open    pay_sched_cur;
3027                 close   pay_sched_cur;
3028 
3029             EXCEPTION
3030                 WHEN NO_DATA_FOUND THEN
3031                     RETURN TRUE; -- assume already processed in this thread
3032                 WHEN locked_by_another_session THEN
3033                     print( p_recursive_level, ' ...locked by another session' );
3034                     RETURN FALSE; -- assume already processed in this thread
3035                 WHEN OTHERS THEN
3036                     print( p_recursive_level, ' ...Failed while trying to lock' );
3037                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3038                     RAISE;
3039             END;
3040 
3041 
3042             /* Bug2472294 : Merged following condition into next one.
3043             --
3044             -- ensure that the transaction is neither a commitment nor
3045             -- related to a commitment
3046             --
3047             DECLARE
3048                 l_commitment_transactions NUMBER;
3049             BEGIN
3050                 SELECT  COUNT(*)
3051                 INTO    l_commitment_transactions
3052                 FROM    ra_customer_trx     ct,
3053                         ra_cust_trx_types   ctt
3054                 WHERE   ct.customer_trx_id = p_entity_id
3055                 AND     ctt.cust_trx_type_id = ct.cust_trx_type_id
3056                 AND
3057                 (
3058                     ctt.type IN ( 'GUAR', 'DEP' )   OR
3059                     ct.initial_customer_trx_id IS NOT NULL
3060                 );
3061                 --
3062                 IF l_commitment_transactions > 0
3063                 THEN
3064                     print( p_recursive_level, '  ...is a commitment or related to a commitment');
3065                     RETURN FALSE;
3066                 END IF;
3067             END;
3068             Bug 2472294 */
3069 
3070 
3071             -- bug2472294 start
3072             -- Handle non post to gl transaction
3073             DECLARE
3074                 l_type ra_cust_trx_types.type%TYPE ;
3075                 l_initial_customer_trx_id ra_customer_trx.initial_customer_trx_id%TYPE;
3076                 l_post_to_gl ra_cust_trx_types.post_to_gl%TYPE;
3077                 l_trx_date ra_customer_trx.trx_date%TYPE;
3078 
3079             BEGIN
3080 
3081                 SELECT  ctt.type,
3082                         ct.initial_customer_trx_id,
3083                         ctt.post_to_gl,
3084                         ct.trx_date
3085                 INTO    l_type,
3086                         l_initial_customer_trx_id,
3087                         l_post_to_gl,
3088                         l_trx_date
3089                 FROM    ra_customer_trx ct,
3090                         ra_cust_trx_types ctt
3091                 WHERE   ct.customer_trx_id = p_entity_id
3092                 AND     ctt.cust_trx_type_id = ct.cust_trx_type_id ;
3093 
3094                 --
3095                 -- ensure that the transaction is neither a commitment nor
3096                 -- related to a commitment
3097                 --
3098                 IF ( l_type = 'GUAR' ) or ( l_type = 'DEP') or
3099                 ( l_initial_customer_trx_id IS NOT NULL )
3100                 THEN
3101                    print( p_recursive_level, '  ...is a commitment or related to a commitment') ;
3102                    RETURN FALSE;
3103                 END IF;
3104 
3105                 IF l_post_to_gl = 'Y'
3106                 THEN
3107                    --
3108                    -- select distributions that are unposted or whose gl_date
3109                    -- is after the purge date
3110                    --
3111                    DECLARE
3112                       l_unpurgeable_distributions   NUMBER;
3113                    BEGIN
3114                       SELECT  COUNT(*)
3115                       INTO    l_unpurgeable_distributions
3116                       FROM    ra_cust_trx_line_gl_dist
3117                       WHERE   customer_trx_id = p_entity_id
3118                       AND     account_set_flag = 'N'
3119                       AND
3120                       (
3121                           posting_control_id = -3    OR
3122                           gl_date > p_as_of_gl_date
3123                       );
3124                       IF l_unpurgeable_distributions <> 0 THEN
3125                          print( p_recursive_level, '  ...which has unpurgeable distributions' );
3126                          RETURN FALSE;
3127                       END IF;
3128                       ---
3129                       ---
3130                    END;
3131                    --
3132                    -- check for adjustments that violate rules
3133                    --    (NOTE: unapproved adjustments are excluded from search)
3134                    --           It is most unlikely that these unapproved adjs.
3135                    --           will be approved. So, these need not be
3136                    --           considered.
3137                    --
3138                    DECLARE
3139                       l_violate_adjustments   NUMBER;
3140                    BEGIN
3141                       SELECT  COUNT(*)
3142                       INTO    l_violate_adjustments
3143                       FROM    ar_adjustments
3144                       WHERE   customer_trx_id = p_entity_id
3145                       AND     status in ('A', 'M', 'W') -- bug1999155
3146                       AND
3147                       (
3148                           posting_control_id = -3    OR
3149                           gl_date            > p_as_of_gl_date
3150                       );
3151                       IF l_violate_adjustments > 0
3152                       THEN
3153                          print( p_recursive_level, '  ...unpurgeable adjustments' );
3154                          RETURN FALSE;
3155                       END IF;
3156                    END;
3157 
3158                 /* l_post_to_gl = 'N'  */
3159                 ELSE
3160 
3161                    IF l_trx_date > p_as_of_gl_date
3162                    THEN
3163                       print( p_recursive_level, '  ...transaction date is after the purge date');
3164                       RETURN FALSE;
3165                    END IF;
3166 
3167                    --
3168                    -- check for adjustments that violate rules
3169                    --    (NOTE: unapproved adjustments are excluded from search)
3170                    --           It is most unlikely that these unapproved adjs.
3171                    --           will be approved. So, these need not be
3172                    --           considered.
3173                    --
3174                    DECLARE
3175                       l_violate_adjustments   NUMBER;
3176                    BEGIN
3177                       SELECT  COUNT(*)
3178                       INTO    l_violate_adjustments
3179                       FROM    ar_adjustments
3180                       WHERE   customer_trx_id = p_entity_id
3181                       AND     status in ('A', 'M', 'W')
3182                       AND decode ( status, 'A', gl_date , p_as_of_gl_date + 1)
3183                              > p_as_of_gl_date ;
3184 
3185                       IF l_violate_adjustments > 0
3186                       THEN
3187                          print( p_recursive_level, '  ...unpurgeable adjustments' );
3188                          RETURN FALSE;
3189                       END IF;
3190                    END;
3191                 END IF;
3192 
3193             EXCEPTION
3194                 WHEN OTHERS THEN
3195                 print( 1, 'Failed while checking the Transaction Type');
3196                 print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3197                 RAISE ;
3198             END ;
3199             -- bug2472294 end
3200 
3201 
3202             --
3203             --
3204             -- Check if this trx. belongs to the same customer
3205             --
3206             DECLARE
3207                 l_same_customer   VARCHAR2(1);
3208             BEGIN
3209 
3210                 IF p_customer_id IS NOT NULL THEN
3211 
3212                    BEGIN
3213                        SELECT  'Y'
3214                        INTO    l_same_customer
3215                        FROM    ra_customer_trx
3216                        WHERE   customer_trx_id = p_entity_id
3217                        AND     bill_to_customer_id = p_customer_id ;
3218 
3219                    EXCEPTION
3220                        WHEN NO_DATA_FOUND THEN
3221                            print( p_recursive_level, '  ...Bill to Customer is different' );
3222                            RETURN FALSE ;
3223                        WHEN OTHERS THEN
3224                            RAISE ;
3225                    END ;
3226                 END IF ;
3227                 --
3228             END;
3229             --
3230             -- check that all of the invoice's payment schedules are closed
3231             --
3232             DECLARE
3233                 l_invoice_open_amount   NUMBER;
3234             BEGIN
3235                 SELECT  NVL(SUM(ABS(amount_due_remaining)),0)
3236                 INTO    l_invoice_open_amount
3237                 FROM    ar_payment_schedules
3238                 WHERE   customer_trx_id = p_entity_id;
3239                 --
3240                 IF l_invoice_open_amount > 0 THEN
3241                     print( p_recursive_level, '  ...payment schedule is not closed' );
3242                     RETURN FALSE;
3243                 END IF;
3244                 --
3245             EXCEPTION
3246                 WHEN OTHERS THEN
3247                     print( 1, 'Failed while checking the Payment Schedules');
3248                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3249                     RAISE ;
3250             END;
3251             --
3252             -- ensure that autorule is complete for this transaction
3253             --
3254             DECLARE
3255                 l_autorule_incomplete_count    NUMBER;
3256             BEGIN
3257                 SELECT  COUNT(*)
3258                 INTO    l_autorule_incomplete_count
3259                 FROM    ra_customer_trx_lines
3260                 WHERE   customer_trx_id        = p_entity_id
3261                 AND     line_type              = 'LINE'
3262                 AND     autorule_complete_flag = 'N';
3263                 IF l_autorule_incomplete_count > 0
3264                 THEN
3265                     print( p_recursive_level, '  ...autorule is not complete' );
3266                     RETURN FALSE;
3267                 END IF;
3268             END;
3269 
3270             /* bug2472294 : Moved to above because this was executed only when
3271                post_to_gl is 'Y'.
3272             --
3273             -- select distributions that are unposted or whose gl_date
3274             -- is after the purge date
3275             --
3276             DECLARE
3277                 l_unpurgeable_distributions   NUMBER;
3278             BEGIN
3279                 SELECT  COUNT(*)
3280                 INTO    l_unpurgeable_distributions
3281                 FROM    ra_cust_trx_line_gl_dist
3282                 WHERE   customer_trx_id = p_entity_id
3283                 AND     account_set_flag = 'N'
3284                 AND
3285                 (
3286                     posting_control_id = -3    OR
3287                     gl_date > p_as_of_gl_date
3288                 );
3289                 IF l_unpurgeable_distributions <> 0 THEN
3290                     print( p_recursive_level, '  ...which has unpurgeable distributions' );
3291                     RETURN FALSE;
3292                 END IF;
3293                 ---
3294                 ---
3295             END;
3296             --
3297             -- check for adjustments that violate rules
3298             --    (NOTE: unapproved adjustments are excluded from search)
3299             --           It is most unlikely that these unapproved adjs.
3300             --           will be approved. So, these need not be
3301             --           considered.
3302             --
3303 
3304             DECLARE
3305                 l_violate_adjustments   NUMBER;
3306             BEGIN
3307                 SELECT  COUNT(*)
3308                 INTO    l_violate_adjustments
3309                 FROM    ar_adjustments
3310                 WHERE   customer_trx_id = p_entity_id
3311                 AND     status in ('A', 'M', 'W') -- bug1999155
3312                 AND
3313                 (
3314                     posting_control_id = -3    OR
3315                     gl_date            > p_as_of_gl_date
3316                 );
3317                 IF l_violate_adjustments > 0
3318                 THEN
3319                     print( p_recursive_level, '  ...unpurgeable adjustments' );
3320                     RETURN FALSE;
3321                 END IF;
3322             END;
3323             bug2472294 */
3324 
3325             --
3326             -- Check if any applications are unpurgeable
3327             --
3328             DECLARE
3329                 l_unpurgeable_applications  NUMBER;
3330             BEGIN
3331                 SELECT  COUNT(*)
3332                 INTO    l_unpurgeable_applications
3333                 FROM    ar_receivable_applications
3334                 WHERE
3335                 (
3336                     applied_customer_trx_id = p_entity_id     OR
3337                     customer_trx_id         = p_entity_id
3338                 )
3339                 AND
3340                 (
3341                     posting_control_id = -3         OR
3342                     gl_date            > p_as_of_gl_date
3343                 )
3344                 AND postable = 'Y' ; -- bug3404430 added to check only postable
3345                 IF l_unpurgeable_applications > 0 THEN
3346                     print( p_recursive_level, '  ...unpurgeable applications' );
3347                     RETURN FALSE;
3348                 END IF;
3349             END;
3350             --
3351 
3352             DECLARE
3353                 l_receivable_amount  NUMBER ;
3354                 l_adjustment_amount  NUMBER ;
3355             BEGIN
3356 
3357                 SELECT acctd_amount
3358                 INTO   l_receivable_amount
3359                 FROM   RA_CUST_TRX_LINE_GL_DIST
3360                 WHERE  customer_trx_id = p_entity_id
3361                 AND    account_class   = 'REC'
3362                 AND    latest_rec_flag = 'Y'  ;
3363 
3364                 p_running_total := p_running_total + l_receivable_amount ;
3365 
3366                 SELECT NVL(SUM(acctd_amount),0)
3367                 INTO   l_adjustment_amount
3368                 FROM   ar_adjustments
3369                 WHERE  customer_trx_id = p_entity_id
3370                 AND    status in ('A', 'M', 'W') ;  -- bug1999155
3371 
3372                 p_running_total := p_running_total + l_adjustment_amount;
3373 
3374             EXCEPTION
3375                   /* bug1999155 No need to handle NO_DATA_FOUND error
3376                   WHEN NO_DATA_FOUND THEN
3377                       RETURN FALSE;
3378 		  */
3379                   WHEN OTHERS THEN
3380                       print( 1, 'Failed while checking GL_DIST/ADJ');
3381                       print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3382                       RAISE;
3383             END ;
3384             -- bug3873165 Added following check
3385             --
3386             -- check if line revenue is completed
3387             --
3388 
3389             DECLARE
3390                 l_line_revenue     NUMBER;
3391             BEGIN
3392                 SELECT  COUNT(*)
3393                 INTO    l_line_revenue
3394                 FROM    ar_deferred_lines dl
3395                 WHERE   p_entity_id = dl.customer_trx_id
3396                 AND     dl.line_collectible_flag = 'N'
3397                 AND     dl.manual_override_flag = 'N'
3398                 AND     dl.acctd_amount_due_original <> dl.acctd_amount_recognized;
3399 
3400                 IF  l_line_revenue > 0
3401                 THEN
3402                     print( p_recursive_level, '  ...line revenue is not completed ' );
3403                     RETURN FALSE;
3404                 END IF;
3405             END;
3406             --
3407             DECLARE
3408                 l_batch_id NUMBER(15) ;
3409                 l_adj_key_value_list      gl_ca_utility_pkg.r_key_value_arr;
3410                 l_ra_batch_key_value_list gl_ca_utility_pkg.r_key_value_arr;
3411                 l_ar_ps_key_value_list    gl_ca_utility_pkg.r_key_value_arr;
3412 		l_ar_dist_key_value_list  gl_ca_utility_pkg.r_key_value_arr;
3413 		l_gl_dist_key_value_list  gl_ca_utility_pkg.r_key_value_arr;
3414 
3415                 /* bug2021662 : added for getting deleted correspondence_id */
3416                 TYPE Del_Cid_Tab IS TABLE OF ar_correspondences.correspondence_id%TYPE INDEX BY BINARY_INTEGER;
3417                 del_cid Del_Cid_Tab;
3418 
3419                 l_corr_row   BINARY_INTEGER := 0 ;
3420 
3421             BEGIN
3422                 --
3423                 -- Archive rows here before deleting so that
3424                 -- you don't lose the data
3425                 --
3426                 archive( l_archive_id,
3427                          p_entity_id,
3428                          p_archive_level,
3429                          l_archive_status) ;
3430 
3431                 IF l_archive_status = FALSE
3432                 THEN
3433                     print( 0,'Archive Failed') ;
3434                     RETURN ( FALSE ) ;
3435                 END IF ;
3436                 --
3437                 SELECT bat.batch_id
3438                 INTO   l_batch_id
3439                 FROM   ra_batches bat,
3440                        ra_customer_trx trx
3441                 WHERE  trx.customer_trx_id = p_entity_id
3442                 AND    trx.batch_id = bat.batch_id (+)
3443                 FOR    UPDATE OF bat.batch_id NOWAIT ;
3444                 --
3445                 -- bug3975105 added 'N'
3446                 print( p_recursive_level, '  ...deleting rows', 'N' );
3447                 --
3448                 /* bug3873165 added two tables for line rev */
3449                 DELETE FROM ar_line_conts
3450                 WHERE  customer_trx_line_id in ( select customer_trx_line_id
3451                                       from   ra_customer_trx
3452                                       where  customer_trx_id = p_entity_id );
3453                 --
3454                 DELETE FROM ar_deferred_lines
3455                 WHERE  customer_trx_id = p_entity_id;
3456                 --
3457                 DELETE FROM ra_customer_trx_lines
3458                 WHERE  customer_trx_id = p_entity_id;
3459                 --
3460                 DELETE FROM ra_cust_trx_line_gl_dist
3461                 WHERE  customer_trx_id = p_entity_id
3462                 RETURNING cust_trx_line_gl_dist_id
3463                 BULK COLLECT INTO l_gl_dist_key_value_list;
3464 
3465                  /*---------------------------------+
3466                  | Calling central MRC library     |
3467                  | for MRC Integration             |
3468                  +---------------------------------*/
3469 
3470              /*   ar_mrc_engine.maintain_mrc_data(
3471                         p_event_mode        => 'DELETE',
3472                         p_table_name        => 'RA_CUST_TRX_LINE_GL_DIST',
3473                         p_mode              => 'BATCH',
3474                         p_key_value_list    => l_gl_dist_key_value_list);*/
3475 
3476                 --
3477                 -- bug 1404679 : to prevent ORA-1403 error when client uses AX,
3478                 -- delete from RA_CUSTOMER_TRX
3479                 -- after lines and dist table are done
3480                 --
3481                 -- DELETE FROM ra_customer_trx
3482                 -- WHERE  customer_trx_id = p_entity_id;
3483                 --
3484 
3485                 -- Call table handler instead of doing direct delete to
3486                 -- ra_customer_Trx
3487 
3488                  arp_ct_pkg.delete_p(p_entity_id);
3489 
3490                 DELETE FROM ra_batches
3491                 WHERE  batch_id = l_batch_id
3492                 AND    NOT EXISTS ( SELECT 'x'
3493                                     FROM   ra_customer_trx t
3494                                     WHERE  t.batch_id = l_batch_id )
3495                 RETURNING batch_id
3496                 BULK COLLECT INTO l_ra_batch_key_value_list;
3497 
3498                 -- bug3283678 this must be done after above delete stmt.
3499                 IF SQL%ROWCOUNT = 0
3500                 THEN
3501                      UPDATE ra_batches batch
3502                      SET    batch.purged_children_flag = 'Y'
3503                      WHERE  batch.batch_id = l_batch_id ;
3504                 END IF ;
3505                 --
3506 
3507                  /*---------------------------------+
3508                  | Calling central MRC library     |
3509                  | for MRC Integration             |
3510                  +---------------------------------*/
3511 
3512              /*   ar_mrc_engine.maintain_mrc_data(
3513                         p_event_mode        => 'DELETE',
3514                         p_table_name        => 'RA_BATCHES',
3515                         p_mode              => 'BATCH',
3516                         p_key_value_list    => l_ra_batch_key_value_list);*/
3517 
3518                 --
3519                 DELETE FROM ar_distributions
3520                 WHERE  source_id in ( select adjustment_id
3521                                       from   ar_adjustments
3522                                       where  customer_trx_id = p_entity_id )
3523                 AND    source_table = 'ADJ'
3524 		RETURNING line_id
3525                 BULK COLLECT INTO l_ar_dist_key_value_list;
3526 
3527                 /*---------------------------------+
3528                  | Calling central MRC library     |
3529                  | for MRC Integration             |
3530                  +---------------------------------*/
3531 
3532               /*  ar_mrc_engine.maintain_mrc_data(
3533                         p_event_mode        => 'DELETE',
3534                         p_table_name        => 'AR_DISTRIBUTIONS',
3535                         p_mode              => 'BATCH',
3536                         p_key_value_list    => l_ar_dist_key_value_list);*/
3537 
3538                 --
3539 
3540                 DELETE FROM ar_adjustments
3541                 WHERE  customer_trx_id = p_entity_id
3542                 RETURNING adjustment_id
3543                 BULK COLLECT INTO l_adj_key_value_list;
3544 
3545                  /*---------------------------------+
3546                  | Calling central MRC library     |
3547                  | for MRC Integration             |
3548                  +---------------------------------*/
3549 
3550                /* ar_mrc_engine.maintain_mrc_data(
3551                         p_event_mode        => 'DELETE',
3552                         p_table_name        => 'AR_ADJUSTMENTS',
3553                         p_mode              => 'BATCH',
3554                         p_key_value_list    => l_adj_key_value_list);*/
3555                 --
3556                 DELETE FROM ra_cust_trx_line_salesreps
3557                 WHERE  customer_trx_id = p_entity_id;
3558                 --
3559                 DELETE FROM ar_notes
3560                 WHERE  customer_trx_id = p_entity_id;
3561                 --
3562                 DELETE FROM ar_action_notifications action
3563                 WHERE  call_action_id IN
3564                 (
3565                      SELECT call.call_action_id
3566                      FROM   ar_call_actions call,
3567                             ar_customer_call_topics topics
3568                      WHERE  topics.customer_trx_id = p_entity_id
3569                      AND    topics.customer_call_topic_id =
3570                                 call.customer_call_topic_id
3571                 ) ;
3572                 --
3573                 DELETE FROM ar_call_actions call
3574                 WHERE  customer_call_topic_id IN
3575                 (
3576                      SELECT topics.customer_call_topic_id
3577                      FROM   ar_customer_call_topics topics
3578                      WHERE  topics.customer_trx_id = p_entity_id
3579                 ) ;
3580                 --
3581                 DELETE FROM ar_customer_call_topics
3582                 WHERE  customer_trx_id = p_entity_id ;
3583                 --
3584                 UPDATE ar_correspondences corr
3585                 SET    corr.purged_children_flag = 'Y'
3586                 WHERE  corr.correspondence_id IN
3587                 (
3588                       SELECT sched.correspondence_id
3589                       FROM   ar_payment_schedules ps,
3590                              ar_correspondence_pay_sched sched
3591                       WHERE  ps.customer_trx_id = p_entity_id
3592                       AND    ps.payment_schedule_id =
3593                                  sched.payment_schedule_id
3594                 ) ;
3595                 --
3596                 /* bug2021662 :add RETURNING to get deleted correspondence_id
3597                 */
3598                 DELETE FROM  ar_correspondence_pay_sched sched
3599                 WHERE  payment_schedule_id IN
3600                 (
3601                       SELECT payment_schedule_id
3602                       FROM   ar_payment_schedules
3603                       WHERE  customer_trx_id = p_entity_id
3604                 )
3605                 RETURNING correspondence_id BULK COLLECT INTO del_cid ;
3606                 --
3607                 /* bug2021662 :this DELETE stmt does not work correctly
3608                 DELETE FROM  ar_correspondences corr
3609                 WHERE  corr.correspondence_id NOT IN
3610                 (
3611                       SELECT sched.correspondence_id
3612                       FROM   ar_correspondence_pay_sched sched,
3613                              ar_payment_schedules ps
3614                       WHERE  ps.customer_trx_id = p_entity_id
3615                       AND    ps.payment_schedule_id =
3616                                  sched.payment_schedule_id
3617                 ) ;
3618                 */
3619                 /* bug2021662 : instead of above stmt, created following stmt
3620 		   for gotton correspondence_id
3621                 */
3622 		IF del_cid.count > 0 THEN
3623                    FORALL l_corr_row IN del_cid.FIRST..del_cid.LAST
3624                    DELETE FROM ar_correspondences corr
3625                    WHERE not exists
3626                    (
3627                       SELECT 'there are children records'
3628                         FROM ar_correspondence_pay_sched sched
3629                        WHERE corr.correspondence_id = sched.correspondence_id )
3630                    AND corr.correspondence_id = del_cid(l_corr_row) ;
3631 		END IF;
3632                 --
3633                 DELETE FROM ar_payment_schedules
3634                 WHERE  customer_trx_id = p_entity_id
3635                  RETURNING payment_schedule_id
3636                 BULK COLLECT INTO l_ar_ps_key_value_list;
3637 
3638                  /*---------------------------------+
3639                  | Calling central MRC library     |
3640                  | for MRC Integration             |
3641                  +---------------------------------*/
3642 
3643                /* ar_mrc_engine.maintain_mrc_data(
3644                         p_event_mode        => 'DELETE',
3645                         p_table_name        => 'AR_PAYMENT_SCHEDULES',
3646                         p_mode              => 'BATCH',
3647                         p_key_value_list    => l_ar_ps_key_value_list);*/
3648 
3649                 --
3650             EXCEPTION
3651                 WHEN NO_DATA_FOUND THEN
3652                     print( p_recursive_level, ' ...No rows found while attempting to lock' );
3653                     RETURN FALSE;
3654                 WHEN locked_by_another_session THEN
3655                     print( p_recursive_level, ' ...locked by another session' );
3656                     RETURN FALSE;
3657                 WHEN deadlock_detected THEN
3658                     print( p_recursive_level, ' ...deadlock detected while deleting trxs.' );
3659                     RETURN FALSE;
3660                 WHEN OTHERS THEN
3661                     print( 1, 'Failed while deleting from the trx tables');
3662                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3663                     RAISE ;
3664             END;
3665             --
3666             -- Recursively deal with applications
3667             --
3668             DECLARE
3669                 CURSOR app_to_invoice( cp_applied_invoice_id NUMBER ) IS
3670                        SELECT  DECODE( application_type,
3671                                          'CASH',cash_receipt_id,
3672                                          'CM'  ,DECODE( applied_customer_trx_id,
3673                                                         cp_applied_invoice_id,
3674                                                         customer_trx_id ,
3675                                                         applied_customer_trx_id ) ),
3676 
3677                                applied_customer_trx_id,
3678                                application_type,
3679                                -- bug1199027
3680                                -- bug4060025 added code for CM app ex gain/loss
3681                                DECODE( application_type,
3682                                         'CASH', acctd_amount_applied_to,
3683                                         'CM', acctd_amount_applied_from - acctd_amount_applied_to ),
3684                                NVL(acctd_earned_discount_taken,0) +
3685                                    NVL(acctd_unearned_discount_taken,0)
3686                        FROM    ar_receivable_applications
3687                        WHERE
3688                        (
3689                            applied_customer_trx_id = cp_applied_invoice_id    OR
3690                            customer_trx_id         = cp_applied_invoice_id
3691                        )
3692                        FOR UPDATE OF receivable_application_id NOWAIT ;
3693 
3694                 -- bug 1715258
3695                 --
3696                 -- Select all invoice related with unpurgeable receipt
3697                 -- to add unpurgeable trx list.
3698                 --
3699                 CURSOR app_to_invoice_receipt( cp_cash_receipt_id NUMBER ) IS
3700                        SELECT applied_customer_trx_id
3701                        FROM   ar_receivable_applications
3702                        WHERE  cash_receipt_id = cp_cash_receipt_id
3703                        AND    status = 'APP';
3704 
3705                 l_application_id           NUMBER; -- receipt_id or trx_id
3706                 l_applied_customer_trx_id  NUMBER;
3707                 l_application_type         ar_receivable_applications.application_type%TYPE;
3708                 l_receipt_amount           NUMBER;
3709                 l_discount_amount          NUMBER;
3710 		l_ar_dist_key_value_list   gl_ca_utility_pkg.r_key_value_arr;
3711                 l_rec_app_key_value_list   gl_ca_utility_pkg.r_key_value_arr;
3712             BEGIN
3713                 OPEN app_to_invoice( p_entity_id );
3714                 --
3715                 DELETE FROM ar_distributions
3716                 WHERE  source_id in ( SELECT receivable_application_id
3717                                       FROM   ar_receivable_applications
3718                                       WHERE
3719                                       (   applied_customer_trx_id = p_entity_id OR
3720                                           customer_trx_id = p_entity_id
3721                                       )
3722                                     )
3723                 AND    source_table = 'RA'
3724 		RETURNING line_id
3725                 BULK COLLECT INTO l_ar_dist_key_value_list;
3726 
3727 
3728                  /*---------------------------------+
3729                  | Calling central MRC library     |
3730                  | for MRC Integration             |
3731                  +---------------------------------*/
3732 
3733                /* ar_mrc_engine.maintain_mrc_data(
3734                         p_event_mode        => 'DELETE',
3735                         p_table_name        => 'AR_DISTRIBUTIONS',
3736                         p_mode              => 'BATCH',
3737                         p_key_value_list    => l_ar_dist_key_value_list);*/
3738 
3739                 --
3740                 DELETE FROM ar_receivable_applications
3741                 WHERE
3742                 (
3743                     applied_customer_trx_id = p_entity_id    OR
3744                     customer_trx_id         = p_entity_id
3745                 )
3746                 RETURNING receivable_application_id
3747                 BULK COLLECT INTO l_rec_app_key_value_list;
3748 
3749                 /*---------------------------------+
3750                  | Calling central MRC library     |
3751                  | for MRC Integration             |
3752                  +---------------------------------*/
3753 
3754                /* ar_mrc_engine.maintain_mrc_data(
3755                         p_event_mode        => 'DELETE',
3756                         p_table_name        => 'AR_RECEIVABLE_APPLICATIONS',
3757                         p_mode              => 'BATCH',
3758                         p_key_value_list    => l_rec_app_key_value_list);*/
3759                 --
3760                 LOOP
3761                     FETCH app_to_invoice
3762                     INTO  l_application_id,
3763                           l_applied_customer_trx_id,
3764                           l_application_type,
3765                           l_receipt_amount,
3766                           l_discount_amount ;
3767                     EXIT WHEN app_to_invoice%NOTFOUND;
3768                     --
3769                     -- This check is made so that it doesn't attempt
3770                     -- to delete again and again within this loop
3771                     --
3772                     IF l_application_type = 'CASH'
3773                     THEN
3774                         ---
3775                         p_running_total := p_running_total - l_receipt_amount
3776                                                 - l_discount_amount ;
3777                         ---
3778                         IF NOT recursive_purge( l_application_id,
3779                                                 'CR',
3780                                                 p_as_of_gl_date,
3781                                                 p_customer_id,
3782                                                 p_archive_level,
3783                                                 p_recursive_level+1,
3784                                                 p_running_total )
3785                         THEN
3786                             CLOSE app_to_invoice;
3787 
3788                             -- bug 1715258
3789                             add_to_unpurgeable_receipts( l_application_id );
3790 
3791                             -- bug 1715258
3792                             --
3793                             -- Add transaction related with unpurgeable receipt
3794                             -- to unpurgeable trx list
3795                             --
3796                             FOR r_app_to_invoice_receipt IN app_to_invoice_receipt(l_application_id )
3797                             LOOP
3798                               IF NOT in_unpurgeable_txn_list( r_app_to_invoice_receipt.applied_customer_trx_id )
3799                               THEN
3800                                 -- bug3975105 added 'N'
3801                                 print( p_recursive_level, '  Add id:' || r_app_to_invoice_receipt.applied_customer_trx_id || ' to unpurgeable transaction list', 'N');
3802                                 add_to_unpurgeable_txns(r_app_to_invoice_receipt.applied_customer_trx_id );
3803                               END IF;
3804 
3805                             END LOOP;
3806 
3807                             RETURN FALSE;
3808                         END IF;
3809                     ELSE
3810                         -- Bug4060025 Need to calc exchange gain/loss for CM
3811                         ---
3812                         p_running_total := p_running_total + l_receipt_amount ;
3813                         ---
3814                         IF NOT recursive_purge( l_application_id,
3815                                                 'CT',
3816                                                 p_as_of_gl_date,
3817                                                 p_customer_id,
3818                                                 p_archive_level,
3819                                                 p_recursive_level+1,
3820                                                 p_running_total )
3821                         THEN
3822                             CLOSE app_to_invoice;
3823                             add_to_unpurgeable_txns( l_applied_customer_trx_id );
3824                             RETURN FALSE;
3825                         END IF;
3826                     END IF;
3827                 END LOOP;
3828                 CLOSE app_to_invoice;
3829             EXCEPTION
3830                 WHEN locked_by_another_session THEN
3831                     print( p_recursive_level, ' ...locked by another session' );
3832                     RETURN FALSE; -- assume already processed in this thread
3833                 WHEN deadlock_detected THEN
3834                     print( p_recursive_level, ' ...deadlock detected in app_to_inv' );
3835                     RETURN FALSE;
3836                 WHEN OTHERS THEN
3837                     print(0,'Failed while dealing with Trx.') ;
3838                     print(0,'Error ' || SQLCODE || ' ' || SQLERRM ) ;
3839                     RAISE ;
3840             END;
3841             RETURN TRUE;
3842             -- finished 'CT' case
3843         ELSIF p_entity_type = 'CR'
3844         THEN
3845             --
3846             -- lock the receipt
3847             --
3848 
3849             -- bug 1715258
3850             IF in_unpurgeable_receipt_list( p_entity_id )
3851             THEN
3852                 -- bug3975105 added 'S'
3853                 print( p_recursive_level, '  ...already in unpurgeable receipt list', 'S');
3854                 RETURN FALSE;
3855             END IF;
3856 
3857             DECLARE
3858                 l_record_found  VARCHAR2(10) := 'Not Found' ;
3859 
3860                 /* bug1999155: Divided select stmt which lock all transactions
3861                   records into the following stmts */
3862                 cursor dist_crh_cur is
3863                     select  'Found'  record_found
3864                     FROM    ar_distributions        dist,
3865                             ar_cash_receipt_history crh
3866                     where   crh.cash_receipt_history_id = dist.source_id (+)
3867                     AND     crh.cash_receipt_id         = p_entity_id
3868                     FOR     UPDATE OF crh.cash_receipt_id,
3869                                       dist.source_id NOWAIT;
3870 
3871                 cursor ps_cur is
3872                     select  'Found'  record_found
3873                     FROM    ar_payment_schedules ps
3874                     where   ps.cash_receipt_id  = p_entity_id
3875                     FOR     UPDATE OF ps.cash_receipt_id  NOWAIT;
3876 
3877                 cursor ra_cur is
3878                     select  'Found'  record_found
3879                     FROM    ar_receivable_applications ra
3880                     where   ra.cash_receipt_id  = p_entity_id
3881                     FOR     UPDATE OF ra.cash_receipt_id  NOWAIT;
3882 
3883                 cursor cr_cur is
3884                     select  'Found'  record_found
3885                     FROM    ar_cash_receipts  cr
3886                     where   cr.cash_receipt_id  = p_entity_id
3887                     FOR     UPDATE OF cr.cash_receipt_id  NOWAIT;
3888 
3889             BEGIN
3890                 -- lock all the transaction records
3891                 /* bug1999155: Divided the following select stmt into
3892                   some stmts. This cursor for loop is not used .
3893                 FOR lock_rec IN (
3894                                   SELECT 'Found'  record_found
3895                                   FROM   ar_distributions dist,
3896                                          ar_payment_schedules ps,
3897                                          ar_receivable_applications ra,
3898                                          ar_cash_receipt_history crh,
3899                                          ar_cash_receipts cr
3900                                   WHERE  cr.cash_receipt_id = p_entity_id
3901                                   AND    cr.cash_receipt_id = crh.cash_receipt_id
3902                                   AND    cr.cash_receipt_id = ra.cash_receipt_id (+)
3903                                   AND    crh.cash_receipt_history_id = dist.source_id (+)
3904                                   AND    cr.cash_receipt_id = ps.cash_receipt_id (+)
3905                                   FOR    UPDATE OF cr.cash_receipt_id,
3906                                                    crh.cash_receipt_id,
3907                                                    ra.cash_receipt_id,
3908                                                    dist.source_id,
3909                                                    ps.cash_receipt_id NOWAIT
3910                                )
3911                 LOOP
3912                     l_record_found := lock_rec.record_found ;
3913                 END LOOP ;
3914                 bug1999155 end */
3915 
3916                 /* bug1999155 : Open created cursors to lock */
3917                 open    dist_crh_cur;
3918 
3919                 fetch   dist_crh_cur
3920                 into l_record_found;
3921 
3922                 --
3923                 -- Need to verify if NO_DATA_FOUND will be raised if
3924                 -- the cursor does not return any row.
3925                 --
3926                 IF l_record_found = 'Not Found'
3927                 THEN
3928                    RETURN TRUE ; -- No Data Found
3929                 END IF ;
3930 
3931                 close   dist_crh_cur;
3932 
3933                 open ps_cur;
3934                 close ps_cur;
3935 
3936                 open ra_cur;
3937                 close ra_cur;
3938 
3939                 open cr_cur;
3940                 close cr_cur;
3941 
3942             EXCEPTION
3943                 -- This receipt has already been deleted by an earlier process
3944                 -- Ideal case when 2 invoices I1 and I2 have the same receipt R1
3945                 -- applied against it.
3946                 WHEN NO_DATA_FOUND THEN
3947                     RETURN TRUE; -- assume already processed in this thread
3948                 WHEN locked_by_another_session THEN
3949                     print( p_recursive_level, ' ...locked by another session' );
3950                     RETURN FALSE; -- assume already processed in this thread
3951                 WHEN OTHERS THEN
3952                     print( p_recursive_level, ' ...Failed while trying to lock CR' );
3953                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
3954                     RAISE;
3955             END;
3956             --
3957             --  Check if it paid by the same customer
3958             --
3959             DECLARE
3960                 l_same_customer  VARCHAR2(1);
3961             BEGIN
3962                 IF p_customer_id IS NOT NULL THEN
3963                     BEGIN
3964                         SELECT  'Y'
3965                         INTO    l_same_customer
3966                         FROM    ar_cash_receipts
3967                         WHERE   cash_receipt_id = p_entity_id
3968                         AND     NVL( pay_from_customer, p_customer_id ) = p_customer_id ;
3969                     EXCEPTION
3970                         WHEN NO_DATA_FOUND THEN
3971                             print( p_recursive_level, ' ...Pymt made by different customer' );
3972                             RETURN FALSE ;
3973                         WHEN OTHERS THEN
3974                             print( p_recursive_level, ' ...Oracle Error at Cust Id. Check' );
3975                             RAISE;
3976                     END ;
3977                 --
3978                 END IF ;
3979             END;
3980             --
3981             -- check if open/closed
3982             --
3983             DECLARE
3984                 l_ps_status    VARCHAR2(2);
3985             BEGIN
3986                 SELECT  status
3987                 INTO    l_ps_status
3988                 FROM    ar_payment_schedules
3989                 WHERE   cash_receipt_id = p_entity_id
3990                 FOR     UPDATE OF payment_schedule_id NOWAIT ;
3991 
3992                 IF l_ps_status = 'OP'  THEN
3993                     print( p_recursive_level,'  ...still open' );
3994                     RETURN FALSE;
3995                 END IF;
3996 
3997             EXCEPTION
3998                 WHEN locked_by_another_session THEN
3999                     print( p_recursive_level, ' ...pymt_sch locked by another session' );
4000                     RETURN ( FALSE ) ;
4001 
4002             END;
4003             -- search for unpurgeable history records
4004             DECLARE
4005                 l_unpurgeable_histories   NUMBER;
4006             BEGIN
4007                 SELECT  COUNT(*)
4008                 INTO    l_unpurgeable_histories
4009                 FROM    ar_cash_receipt_history
4010                 WHERE   cash_receipt_id = p_entity_id
4011                 AND
4012                 (
4013                     posting_control_id = -3          OR
4014                     gl_date > p_as_of_gl_date
4015                 );
4016                 --
4017                 IF l_unpurgeable_histories >0  THEN
4018                     print( p_recursive_level, '  ...unpurgeable CRH exist' );
4019                     RETURN FALSE;
4020                 END IF;
4021                 -- 5715943
4022                 SELECT COUNT(*)
4023                 INTO   l_unpurgeable_histories
4024                 FROM   ar_cash_receipt_history
4025                 WHERE  cash_receipt_id = p_entity_id
4026                 AND    current_record_flag = 'Y'
4027                 AND
4028                 (
4029                      ( status =  'CLEARED' AND factor_flag = 'Y' ) OR
4030                      ( status IN ( 'APPROVED', 'REMITTED', 'CONFIRMED', 'REVERSED' ) )
4031                 ) ;
4032                 --
4033                 -- 5715943
4034                 IF l_unpurgeable_histories > 0 THEN
4035                     print( p_recursive_level, '  ...which has unpurgeable histories' );
4036                     RETURN FALSE;
4037                 END IF;
4038             END;
4039             --
4040             -- check if there are any applications
4041             --
4042 
4043             DECLARE
4044                 l_unpurgeable_applications     NUMBER;
4045             BEGIN
4046                 SELECT  COUNT(*)
4047                 INTO    l_unpurgeable_applications
4048                 FROM    ar_receivable_applications
4049                 WHERE   cash_receipt_id = p_entity_id
4050                 AND
4051                 (
4052                     posting_control_id = -3       OR
4053                     gl_date            > p_as_of_gl_date
4054                 );
4055 
4056                 IF  l_unpurgeable_applications > 0
4057                 THEN
4058                     print( p_recursive_level, '  ...unpurgeable applications' );
4059                     RETURN FALSE;
4060                 END IF;
4061             END;
4062             -- bug3655859 Added following check
4063             --
4064             -- check if there are related bank statement in CE
4065             --
4066 
4067             DECLARE
4068                 l_statement_reconciliation     NUMBER;
4069             BEGIN
4070                 SELECT  COUNT(*)
4071                 INTO    l_statement_reconciliation
4072                 FROM    ar_cash_receipt_history crh,
4073                         ce_statement_reconciliations sr
4074                 WHERE   cash_receipt_id = p_entity_id
4075                 AND     crh.cash_receipt_history_id = sr.reference_id
4076                 AND     sr.reference_type = 'RECEIPT'
4077                 AND     sr.current_record_flag = 'Y'
4078                 AND     sr.status_flag = 'M' ;
4079 
4080                 IF  l_statement_reconciliation > 0
4081                 THEN
4082                     print( p_recursive_level, '  ...bank statement exists in CE ' );
4083                     RETURN FALSE;
4084                 END IF;
4085             END;
4086             --
4087             -- delete records
4088             --
4089             DECLARE
4090 		-- bug3384792 added
4091 		TYPE BatchTyp IS TABLE OF NUMBER(15) INDEX BY BINARY_INTEGER;
4092                 l_batch_id  BatchTyp ;
4093                 l_batch_id_null  BatchTyp ;
4094                 l_trans_id NUMBER(15) ;
4095 
4096                 l_rate_adj_key_value_list  gl_ca_utility_pkg.r_key_value_arr;
4097                 l_ar_batch_key_value_list  gl_ca_utility_pkg.r_key_value_arr;
4098                 l_ar_ps_key_value_list     gl_ca_utility_pkg.r_key_value_arr;
4099 		l_ar_dist_key_value_list   gl_ca_utility_pkg.r_key_value_arr;
4100 
4101                 --
4102                 -- lock ar_batches row before deleting
4103                 --
4104 		-- bug33843792 removed outer join and changed to cursor
4105 		CURSOR cur_batch_id(l_receipt_id NUMBER) IS
4106                 SELECT bat.batch_id
4107                 FROM   ar_batches bat,
4108                        (SELECT distinct batch_id
4109 			FROM ar_cash_receipt_history
4110                 	WHERE  cash_receipt_id = l_receipt_id) crh
4111                	WHERE   crh.batch_id = bat.batch_id
4112                 FOR    UPDATE OF bat.batch_id NOWAIT ;
4113 		--
4114 		CURSOR cur_trans_id(l_receipt_id NUMBER) IS
4115                 SELECT bat.transmission_request_id
4116                 FROM   ar_batches bat,
4117                        ar_cash_receipt_history crh
4118                 WHERE  crh.cash_receipt_id = l_receipt_id
4119                 AND    crh.batch_id = bat.batch_id
4120 		AND    crh.first_posted_record_flag = 'Y';
4121 
4122             BEGIN
4123                 -- bug3384792 get batch info
4124 		OPEN cur_batch_id(p_entity_id) ;
4125 		FETCH cur_batch_id BULK COLLECT INTO l_batch_id ;
4126 		CLOSE cur_batch_id ;
4127                 --
4128 		OPEN cur_trans_id(p_entity_id) ;
4129 		FETCH cur_trans_id INTO l_trans_id ;
4130 		CLOSE cur_trans_id ;
4131                 --
4132                 -- bug3975105 added 'N'
4133                 print( p_recursive_level, '  ...deleting rows', 'N');
4134                 --
4135                 -- Call entity handler to delete from ar_cash_Receipts.
4136                 -- DELETE FROM ar_cash_receipts
4137                 -- WHERE  cash_receipt_id = p_entity_id;
4138                 ARP_CASH_RECEIPTS_PKG.DELETE_P(p_entity_id);
4139 
4140                 --
4141                 DELETE FROM ar_distributions
4142                 WHERE  source_id in
4143                 (
4144                   SELECT cash_receipt_history_id
4145                   FROM   ar_cash_receipt_history
4146                   WHERE  cash_receipt_id = p_entity_id
4147                 )
4148                 AND    source_table = 'CRH'
4149 		RETURNING line_id
4150                 BULK COLLECT INTO l_ar_dist_key_value_list;
4151 
4152                 /*---------------------------------+
4153                  | Calling central MRC library     |
4154                  | for MRC Integration             |
4155                  +---------------------------------*/
4156 
4157                /* ar_mrc_engine.maintain_mrc_data(
4158                         p_event_mode        => 'DELETE',
4159                         p_table_name        => 'AR_DISTRIBUTIONS',
4160                         p_mode              => 'BATCH',
4161                         p_key_value_list    => l_ar_dist_key_value_list);*/
4162 
4163 
4164                 --
4165                 -- Bug 2021718: call the entity handler for
4166                 -- ar_cash_receipt_history rather
4167                 -- then doing the delete in this package.
4168                 -- DELETE FROM ar_cash_receipt_history
4169                 -- WHERE  cash_receipt_id = p_entity_id;
4170 
4171                 arp_cr_history_pkg.delete_p_cr(p_entity_id);
4172 
4173                 --
4174 		-- bug3384792 there could be multiple records for one receipt.
4175 		-- To handle the case, use BULK for delete stmt for ar_batches.
4176 		-- And for performance, check whether or not there is batch.
4177 		IF l_batch_id.COUNT>0
4178 		THEN
4179 		   FORALL i IN l_batch_id.FIRST..l_batch_id.LAST
4180                    DELETE FROM ar_batches
4181                    WHERE  batch_id = l_batch_id(i)
4182                    AND    NOT EXISTS ( SELECT 'x'
4183                                     FROM   ar_cash_receipt_history h
4184                                     WHERE  h.batch_id = l_batch_id(i) )
4185                    RETURNING batch_id
4186                    BULK COLLECT INTO l_ar_batch_key_value_list;
4187 
4188                    --
4189                    -- There could be multiple records within this batch
4190                    -- In this case, the above statement would not delete
4191                    -- this record.
4192                    --
4193 		   FOR j IN l_batch_id.FIRST..l_batch_id.LAST
4194 		   LOOP
4195 		      IF SQL%BULK_ROWCOUNT(j) = 0
4196 		      THEN
4197                          UPDATE ar_batches
4198                          SET purged_children_flag = 'Y'
4199                          WHERE batch_id = l_batch_id(j);
4200 		      END IF;
4201 		   END LOOP;
4202 
4203                    /*---------------------------------+
4204                     | Calling central MRC library     |
4205                     | for MRC Integration             |
4206                     +---------------------------------*/
4207 
4208                   /* ar_mrc_engine.maintain_mrc_data(
4209                         p_event_mode        => 'DELETE',
4210                         p_table_name        => 'AR_BATCHES',
4211                         p_mode              => 'BATCH',
4212                         p_key_value_list    => l_ar_batch_key_value_list);*/
4213 
4214                    --
4215 		   --
4216 		   IF l_trans_id IS NOT NULL
4217 		   THEN
4218 		      DELETE from ar_transmissions trans
4219 		      WHERE  transmission_request_id = l_trans_id
4220 		      AND    NOT EXISTS
4221 		      (
4222 	 	         SELECT '*'
4223 		         FROM ar_batches batch
4224 		         WHERE batch.transmission_request_id = l_trans_id
4225 		      );
4226 		   END IF;
4227 		END IF;
4228 
4229                 --
4230                 DELETE FROM ar_payment_schedules
4231                 WHERE  cash_receipt_id = p_entity_id
4232                 RETURNING payment_schedule_id
4233                 BULK COLLECT INTO l_ar_ps_key_value_list;
4234 
4235                  /*---------------------------------+
4236                  | Calling central MRC library     |
4237                  | for MRC Integration             |
4238                  +---------------------------------*/
4239 
4240                /* ar_mrc_engine.maintain_mrc_data(
4241                         p_event_mode        => 'DELETE',
4242                         p_table_name        => 'AR_PAYMENT_SCHEDULES',
4243                         p_mode              => 'BATCH',
4244                         p_key_value_list    => l_ar_ps_key_value_list);*/
4245 
4246                 --
4247 
4248                 DELETE FROM ar_rate_adjustments
4249                 WHERE  cash_receipt_id = p_entity_id
4250                 RETURNING rate_adjustment_id
4251                 BULK COLLECT INTO l_rate_adj_key_value_list;
4252 
4253                  /*---------------------------------+
4254                  | Calling central MRC library     |
4255                  | for MRC Integration             |
4256                  +---------------------------------*/
4257 
4258               /*  ar_mrc_engine.maintain_mrc_data(
4259                         p_event_mode        => 'DELETE',
4260                         p_table_name        => 'AR_RATE_ADJUSTMENTS',
4261                         p_mode              => 'BATCH',
4262                         p_key_value_list    => l_rate_adj_key_value_list);*/
4263 
4264                 --
4265             EXCEPTION
4266                 WHEN NO_DATA_FOUND THEN
4267                     print( p_recursive_level, ' ...No rows found while attempting to lock' );
4268                     RETURN FALSE;
4269                 WHEN locked_by_another_session THEN
4270                     print( p_recursive_level, ' ...locked by another session' );
4271                     RETURN FALSE;
4272                 WHEN deadlock_detected THEN
4273                     print( p_recursive_level, ' ...deadlock detected while deleting from appls.' );
4274                     RETURN FALSE;
4275                 WHEN OTHERS THEN
4276                     print( 1, 'Failed while deleting from CR tables');
4277                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4278                     RAISE ;
4279             END;
4280             --
4281             -- deal with applications
4282             --
4283             DECLARE
4284                 CURSOR app_from_receipt( cp_cash_receipt_id NUMBER ) IS
4285                        SELECT  applied_customer_trx_id,
4286                                -- bug1199027
4287                                acctd_amount_applied_to,
4288                                NVL(acctd_earned_discount_taken,0) +
4289                                    NVL(acctd_unearned_discount_taken,0),
4290                                NVL(acctd_amount_applied_from,0) -
4291                                    NVL(acctd_amount_applied_to,0),
4292                                gl_date
4293                        FROM    ar_receivable_applications
4294                        WHERE   cash_receipt_id = cp_cash_receipt_id
4295                        AND     status          = 'APP'
4296                        FOR     UPDATE OF receivable_application_id NOWAIT ;
4297 
4298                 l_applied_customer_trx_id  NUMBER;
4299                 l_receipt_amount           NUMBER;
4300                 l_discount_amount          NUMBER;
4301                 l_gain_loss                NUMBER;
4302                 l_gl_date                  DATE;
4303                 l_period_name              VARCHAR2(15) ;
4304                 l_status                   BOOLEAN;
4305                 l_cnt_unapp_rows           NUMBER;
4306 		l_ar_dist_key_value_list  gl_ca_utility_pkg.r_key_value_arr;
4307                 l_rec_app_key_value_list   gl_ca_utility_pkg.r_key_value_arr;
4308 
4309 
4310             BEGIN
4311                 OPEN app_from_receipt( p_entity_id );
4312                 ---
4313                 ---
4314                 LOOP
4315                     FETCH app_from_receipt
4316                     INTO  l_applied_customer_trx_id,
4317                           l_receipt_amount ,
4318                           l_discount_amount,
4319                           l_gain_loss,
4320                           l_gl_date ;
4321                     EXIT  WHEN app_from_receipt%NOTFOUND;
4322                     --
4323                     p_running_total := p_running_total - l_receipt_amount
4324                                            - l_discount_amount ;
4325 
4326                     -- To update ar_archive_control_detail with the
4327                     -- cash receipt amount. This rec. appln. record
4328                     -- will not exist when archive procedure is
4329                     -- called recursively.
4330 
4331                     l_period_name := get_period_name ( l_gl_date );
4332 /* bug1199027
4333                     l_status := ins_control_detail_table ( NVL(l_receipt_amount,0),
4334                                                           'CASH',
4335                                                           'Y',
4336                                                           l_period_name,
4337                                                           l_archive_id  ) ;
4338 
4339                     IF (l_discount_amount <> 0)
4340                     THEN
4341                         l_status := ins_control_detail_table ( l_discount_amount,
4342                                                               'DISC',
4343                                                               'Y',
4344                                                               l_period_name,
4345                                                               l_archive_id  ) ;
4346                     END IF ;
4347 
4348                     IF (l_gain_loss <> 0)
4349                     THEN
4350                         l_status := ins_control_detail_table ( l_gain_loss,
4351                                                               'EXCH',
4352                                                               'Y',
4353                                                               l_period_name,
4354                                                               l_archive_id  ) ;
4355                     END IF ;
4356 */
4357 
4358                     --
4359                     DELETE FROM ar_receivable_applications
4360                     WHERE  cash_receipt_id = p_entity_id
4361                     RETURNING receivable_application_id
4362                     BULK COLLECT INTO l_rec_app_key_value_list;
4363 
4364                     /*---------------------------------+
4365                      | Calling central MRC library     |
4366                      | for MRC Integration             |
4367                      +---------------------------------*/
4368 
4369                   /*  ar_mrc_engine.maintain_mrc_data(
4370                         p_event_mode        => 'DELETE',
4371                         p_table_name        => 'AR_RECEIVABLE_APPLICATIONS',
4372                         p_mode              => 'BATCH',
4373                         p_key_value_list    => l_rec_app_key_value_list);*/
4374 
4375                     --
4376                     IF NOT recursive_purge( l_applied_customer_trx_id,
4377                                             'CT',
4378                                             p_as_of_gl_date,
4379                                             p_customer_id,
4380                                             p_archive_level,
4381                                             p_recursive_level+1,
4382                                             p_running_total )
4383                     THEN
4384                         CLOSE app_from_receipt;
4385                         add_to_unpurgeable_txns( l_applied_customer_trx_id );
4386                         RETURN FALSE;
4387                     END IF;
4388                 END LOOP;
4389                 CLOSE app_from_receipt;
4390                 --
4391                 DELETE FROM ar_distributions
4392                 WHERE  source_id in ( SELECT receivable_application_id
4393                                       FROM   ar_receivable_applications
4394                                       WHERE  cash_receipt_id = p_entity_id
4395                                       AND    status  <> 'APP' )
4396 
4397                 AND    source_table = 'RA'
4398 		RETURNING line_id
4399                 BULK COLLECT INTO l_ar_dist_key_value_list;
4400 
4401 
4402                  /*---------------------------------+
4403                  | Calling central MRC library     |
4404                  | for MRC Integration             |
4405                  +---------------------------------*/
4406 
4407              /*   ar_mrc_engine.maintain_mrc_data(
4408                         p_event_mode        => 'DELETE',
4409                         p_table_name        => 'AR_DISTRIBUTIONS',
4410                         p_mode              => 'BATCH',
4411                         p_key_value_list    => l_ar_dist_key_value_list);*/
4412 
4413                --
4414 
4415                 --
4416                 --  Need to lock the rows for status <> 'APP'.
4417                 --  This delete is necessary to delete all the UNAPP rows
4418                 --  in case of a single receipt applied against a single
4419                 --  invoice.
4420                 --
4421                 BEGIN
4422                     FOR I in ( SELECT receivable_application_id
4423                                FROM   ar_receivable_applications
4424                                WHERE  cash_receipt_id = p_entity_id
4425                                AND    status <> 'APP'
4426                                FOR  UPDATE OF receivable_application_id NOWAIT )
4427                     LOOP
4428                         DELETE FROM ar_receivable_applications
4429                         WHERE  receivable_application_id =
4430                                    I.receivable_application_id;
4431 
4432                 /*---------------------------------+
4433                  | Calling central MRC library     |
4434                  | for MRC Integration             |
4435                  +---------------------------------*/
4436 
4437               /*  ar_mrc_engine.maintain_mrc_data(
4438                         p_event_mode        => 'DELETE',
4439                         p_table_name        => 'AR_RECEIVABLE_APPLICATIONS',
4440                         p_mode              => 'SINGLE',
4441                         p_key_value         => I.receivable_application_id);*/
4442 
4443                         --
4444                     END LOOP ;
4445                 EXCEPTION
4446                     WHEN locked_by_another_session THEN
4447                          print( p_recursive_level, ' ...appl.locked by another session' );
4448                          RETURN FALSE;
4449                     WHEN deadlock_detected THEN
4450                          print( p_recursive_level, ' ...deadlock detected while deleting UNAPP rows
4451 ' );
4452                          RETURN FALSE;
4453                 END ;
4454                 --
4455             EXCEPTION
4456                 WHEN locked_by_another_session THEN
4457                     print( p_recursive_level, ' ...locked by another session' );
4458                     RETURN FALSE;
4459                 WHEN deadlock_detected THEN
4460                     print( p_recursive_level, ' ...deadlock detected in app_from_receipt' );
4461                     RETURN FALSE;
4462                 WHEN OTHERS THEN
4463                     print( p_recursive_level, ' ...Failed while trying to lock rec. app.');
4464                     print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4465                     RAISE ;
4466             END;
4467             RETURN TRUE;
4468         END IF;
4469         RETURN TRUE; -- Not reqd.
4470 
4471     EXCEPTION
4472         WHEN OTHERS THEN
4473             print( 1, 'Failed in Recursive purge') ;
4474             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4475             RAISE ;
4476     END;
4477     --
4478     PROCEDURE drive_by_invoice( errbuf           OUT NOCOPY VARCHAR2,
4479                                 retcode          OUT NOCOPY NUMBER,
4480                                 p_start_gl_date  IN  DATE, --bug1199027
4481                                 p_end_gl_date    IN  DATE, --bug1199027
4482                                 p_as_of_gl_date  IN  DATE, --bug1199027
4483                                 p_archive_level  IN  VARCHAR2,
4484                                 p_archive_id     IN  NUMBER,
4485                                 p_total_worker   IN  NUMBER,
4486                                 p_worker_number  IN  NUMBER,
4487                                 p_customer_id    IN  NUMBER,
4488                                 p_short_flag     IN  VARCHAR2) IS
4489         --
4490         --  Earlier, it was driven from RA_CUST_TRX_LINE_GL_DIST
4491         --  To improve the performance, the code is changed
4492         --  so that it drives from AR_PAYMENT_SCHEDULES.
4493         --  This will not handle the cases where the
4494         --  open_receivable flag for the transaction_type is set
4495         --  to 'N'. This is the intended behaviour to improve
4496         --  the performance.
4497         --
4498         -- bug1199027 Use cp_start/end_gl_date instead of l_as_of_gl_date
4499         CURSOR c_inv( cp_start_gl_date DATE, cp_end_gl_date DATE,
4500                       cp_customer_id   NUMBER ,
4501                       cp_max_trx_id    NUMBER) IS
4502         SELECT ct.customer_trx_id          customer_trx_id
4503         FROM   ra_cust_trx_types           ctt,
4504                ra_customer_trx             ct,
4505                ar_payment_schedules        ps
4506         WHERE  ct.initial_customer_trx_id  IS NULL
4507         AND    ps.customer_trx_id          = ct.customer_trx_id
4508         -- bug1199027
4509         AND    ps.gl_date_closed           BETWEEN cp_start_gl_date
4510                                            AND     cp_end_gl_date
4511         -- bug2967315 added DM
4512         AND    ps.class                    IN ('INV','CM', 'DM')
4513         AND    NVL(cp_customer_id, 0 )     = DECODE(cp_customer_id, NULL,0,
4514                                                  ct.bill_to_customer_id )
4515         AND    ps.terms_sequence_number     = 1
4516         AND    ctt.cust_trx_type_id        = ct.cust_trx_type_id
4517         AND    ctt.type                    NOT IN ('DEP', 'GUAR' )
4518         -- bug2472294
4519         -- AND    ctt.post_to_gl              = 'Y'  -- just handle gl_date < cut-off date
4520         AND    ct.complete_flag = 'Y'
4521         AND    ct.customer_trx_id > cp_max_trx_id  -- bug1715258
4522         ORDER BY ct.customer_trx_id  ;  -- bug1715258
4523 
4524         -- bug1715258
4525         r_inv  c_inv%ROWTYPE ;
4526         l_max_trx_id     NUMBER := 0 ;
4527         l_max_record     NUMBER := 500 ;
4528 
4529         TYPE inv_table IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
4530         l_inv_table      inv_table;
4531         -- bug3990664 added
4532         l_inv_table_null inv_table;
4533         l_inv_rows       BINARY_INTEGER := 0;
4534         l_inv_cnt        BINARY_INTEGER := 0;
4535         l_trx_id         NUMBER ;
4536         -- bug1715258
4537 
4538 
4539         l_running_total  NUMBER ;
4540         l_existence      NUMBER(2) ;
4541         -- l_archive_status BOOLEAN ; --bug1199027
4542         l_arch_status    BOOLEAN ; -- bug1199027
4543         --l_as_of_gl_date  DATE ; -- bug1199027
4544         l_cnt_of_chains  NUMBER := 0 ;
4545         l_org_id         NUMBER ; /* Bug 5290308 */
4546 
4547     BEGIN
4548 
4549 	/*Bug 5349016 Commenting the below code as it is handled in ARARCALL.sql
4550         -- Bug 5290308 : Set the org_context
4551         fnd_profile.get('ORG_ID', l_org_id);
4552         mo_global.init ('AR');
4553         mo_global.set_policy_context('S',l_org_id);
4554         arp_global.init_global(l_org_id);
4555         arp_standard.init_standard(l_org_id);
4556 	*/
4557 
4558         /* bug3975105 added */
4559 	IF p_short_flag = 'Y' THEN
4560            l_short_flag := p_short_flag;
4561 	   print(0,'(Show only unpurged items)');
4562 	END IF;
4563         --
4564         --l_as_of_gl_date := TRUNC(to_date(p_as_of_gl_date,'DD-MON-YYYY'));
4565         -- bug1199027
4566         --l_as_of_gl_date := FND_DATE.canonical_to_date(p_as_of_gl_date) ;
4567         --
4568         l_archive_id := p_archive_id ;
4569         --
4570         print( 0,'Starting Archive and Purge Process');
4571         print( 0,'----------------------------------');
4572         --
4573 
4574         -- bug 1715258
4575         -- Change logic to prevent "Snapshot too old" error
4576         --
4577         LOOP
4578 
4579            l_inv_cnt := 0 ;
4580 
4581            /* 3990664: added initialization */
4582            l_inv_table := l_inv_table_null ;
4583 
4584            -- bug1199027 Use cp_start/end_gl_date instead of l_as_of_gl_date
4585            OPEN c_inv(p_start_gl_date,p_end_gl_date,
4586 				p_customer_id , l_max_trx_id) ;
4587 
4588            -- bug3990664: changed to BULK FETCH
4589               FETCH c_inv BULK COLLECT INTO l_inv_table LIMIT l_max_record;
4590 
4591            CLOSE c_inv ;
4592 
4593            -- bug1715258
4594            -- set max trx id to l_max_trx_id in order not to process
4595            -- same trx id.
4596            -- bug3990664 : added
4597            l_inv_cnt := l_inv_table.COUNT ;
4598 
4599            -- bug3990664 : modified
4600            /* Bug fix 5290308 : Try to access the table only if it contains records */
4601            IF l_inv_cnt  > 0 THEN
4602                l_max_trx_id := l_inv_table(l_inv_table.last) ;
4603            END IF;
4604 
4605            IF l_inv_cnt > 0 THEN
4606               FOR l_inv_rows IN l_inv_table.first..l_inv_table.last LOOP
4607 
4608               BEGIN
4609                 --
4610                 SAVEPOINT prior_to_inv;
4611                 --
4612                 l_running_total := 0 ;
4613                 l_cnt_of_chains := l_cnt_of_chains + 1 ;
4614                 l_trx_id        := l_inv_table(l_inv_rows); -- bug1715258
4615                 l_inv_table.delete(l_inv_rows); -- bug1715258
4616                 --
4617                 -- Just to make sure that this trx is not deleted
4618                 -- by another instance when called recursively
4619                 --
4620                 SELECT 1
4621                 INTO   l_existence
4622                 FROM   RA_CUSTOMER_TRX
4623                 WHERE  customer_trx_id = l_trx_id
4624                 FOR    UPDATE OF customer_trx_id  NOWAIT ;
4625 
4626                 -- lock all the corresponding records
4627 
4628                 IF l_existence = 0 THEN
4629                    print(0, l_trx_id || ' ...already purged by another instance') ;
4630                    GOTO continue ;
4631                 END IF ;
4632     --
4633                 IF recursive_purge( l_trx_id,
4634                                     'CT',
4635                                     p_as_of_gl_date,
4636                                     p_customer_id,
4637                                     p_archive_level,
4638                                     0,
4639                                     l_running_total )
4640                 THEN
4641                     IF l_running_total = 0
4642                     THEN
4643                        -- bug1199027
4644                        l_arch_status := upd_arch_control_detail( p_archive_id ) ;
4645                        l_control_detail_array.delete ;
4646                        --
4647                        -- bug3975105 added 'S'
4648                        print( 0,'Successful purge' , 'S');
4649                        COMMIT;
4650                        --
4651                     ELSE
4652                        print( 1,'...Running total is not Zero ');
4653                        -- bug3975105 added 'N'
4654                        print( 0, 'Rollback work', 'N');
4655                        add_to_unpurgeable_txns( l_trx_id );
4656                        -- bug1199027
4657                        l_control_detail_array.delete ;
4658                        --
4659                        ROLLBACK TO prior_to_inv;
4660                     END IF ;
4661                 ELSE
4662                     -- bug3975105 added 'N'
4663                     print( 0, 'Rollback Work', 'N');
4664                     add_to_unpurgeable_txns( l_trx_id );
4665                     -- bug1199027
4666                     l_control_detail_array.delete ;
4667                     --
4668                     ROLLBACK TO prior_to_inv;
4669                 END IF;
4670                 << continue >>
4671                 -- bug3975105 added 'N'
4672                 print( 0, '------------------------------------------------------------', 'N' );
4673                 IF ( l_cnt_of_chains MOD 500 ) = 0 THEN
4674                      -- bug3975105 added 'N'
4675                      print(0, 'No. of Chains processed so far : ' || l_cnt_of_chains , 'N') ;
4676                      print( 0, '------------------------------------------------------------', 'N' );
4677                 END IF ;
4678               EXCEPTION
4679                 WHEN NO_DATA_FOUND THEN
4680                    print( 0,'Id : ' || l_trx_id ) ;
4681                    print( 0, '...deleted by another instance' );
4682                    print( 0, '------------------------------------------------------------' );
4683                    ROLLBACK TO prior_to_inv; -- bug1999155
4684                    -- bug1199027
4685                    IF ( l_cnt_of_chains MOD 500 ) = 0 THEN
4686                         print(0, 'No. of Chains processed so far : ' || l_cnt_of_chains ) ;
4687                         print( 0, '------------------------------------------------------------' );
4688 		   END IF;
4689                 WHEN locked_by_another_session THEN
4690                    print( 0,'...locked by another session ') ;
4691                    print( 0, '------------------------------------------------------------' );
4692                    ROLLBACK TO prior_to_inv;
4693                    -- bug1199027
4694                    IF ( l_cnt_of_chains MOD 500 ) = 0 THEN
4695                         print(0, 'No. of Chains processed so far : ' || l_cnt_of_chains ) ;
4696                         print( 0, '------------------------------------------------------------' );
4697                    END IF ;
4698                 WHEN savepoint_not_established THEN
4699                    print( 0,'...Savepoint not established') ;
4700                    print( 0, '------------------------------------------------------------' );
4701                    ROLLBACK ; -- bug1999155
4702                    RAISE ;
4703                 WHEN OTHERS THEN
4704                    print( 1, 'Failed in the for loop') ;
4705                    print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4706                    ROLLBACK TO prior_to_inv; -- bug1999155
4707                    RAISE ;
4708               END ;
4709               END LOOP ;
4710 
4711            END IF;
4712 
4713            -- bug1715258
4714            --
4715            -- Exit when already get last record
4716            --
4717            EXIT WHEN l_inv_cnt < l_max_record ;
4718 
4719         END LOOP;
4720         print( 0,'------------------------------------------------------------ ' );
4721         print( 0,'Total No. of Chains Processed : ' || l_cnt_of_chains );
4722         print( 0,'End Time : ' || to_char(sysdate,'dd-mon-yyyy hh:mi:ss') );
4723         print( 0,'------------------------------ End ------------------------- ' );
4724 
4725     EXCEPTION
4726         WHEN OTHERS THEN
4727             print( 1, 'sqlcode = ' || SQLCODE || SQLERRM ) ;
4728             print( 1, 'Failed in drive_by_invoice') ;
4729             ROLLBACK ;
4730             print( 0,'------------------------------------------------------------ ' );
4731             print( 0,'Total No. of Chains Processed : ' || l_cnt_of_chains );
4732             print( 0,'End Time : ' || to_char(sysdate,'dd-mon-yyyy hh:mi:ss') );
4733             print( 0,'------------------------------ End ------------------------- ' );
4734             fnd_file.put_line (FND_FILE.LOG, 'Error ' || SQLCODE || ' ' || SQLERRM ) ;
4735             RAISE ;
4736     END;
4737 
4738 END;