DBA Data[Home] [Help]

PACKAGE BODY: APPS.ARP_ROUNDING

Source


1 PACKAGE BODY ARP_ROUNDING AS
2 /* $Header: ARPLCREB.pls 120.49.12020000.7 2012/09/11 14:37:20 ashlkuma ship $ */
3 
4  /*-------------------------------+
5   |  Global variable declarations |
6   +-------------------------------*/
7 PG_DEBUG varchar2(1) := NVL(FND_PROFILE.value('AFLOG_ENABLED'), 'N');
8 
9   iTRUE  CONSTANT NUMBER  := 1;
10   iFALSE CONSTANT NUMBER  := 0;
11   cr	CONSTANT char(1) := NULL;
12 
13   trx_for_rof           ra_cust_trx_line_gl_dist_all.customer_trx_id%type;
14                         /*Added for Bugs 2480898, 2493896, 2497841 */
15   rqid_for_rof          ra_cust_trx_line_gl_dist_all.request_id%type;
16 
17   /* 7039838 - determines if call is from an autoinvoice inspired
18        session */
19   g_autoinv             BOOLEAN;
20   g_autoinv_request_id  NUMBER;
21 
22   TYPE l_line_id_type IS TABLE OF ra_cust_trx_line_gl_dist_all.customer_trx_line_id%type
23         INDEX BY BINARY_INTEGER;
24   TYPE l_amount_type IS TABLE OF ra_cust_trx_line_gl_dist_all.amount%type
25         INDEX BY BINARY_INTEGER;
26   TYPE l_percent_type IS TABLE OF ra_cust_trx_line_gl_dist_all.percent%type
27         INDEX BY BINARY_INTEGER;
28   TYPE l_acct_class IS TABLE OF ra_cust_trx_line_gl_dist_all.account_class%type
29         INDEX BY BINARY_INTEGER;
30   TYPE l_rec_offset IS TABLE OF ra_cust_trx_line_gl_dist_all.rec_offset_flag%type
31         INDEX BY BINARY_INTEGER;
32   TYPE l_date_type IS TABLE OF ra_cust_trx_line_gl_dist_all.gl_date%type
33         INDEX BY BINARY_INTEGER;
34 
35 -- Private cursor
36 
37   select_sql_c number;
38 
39 -- To hold values fetched from the Select stmt
40 
41 TYPE select_rec_type IS RECORD
42 (
43   rec_customer_trx_id                     BINARY_INTEGER,
44   rec_code_combination_id                 BINARY_INTEGER,
45   round_customer_trx_id                   BINARY_INTEGER
46 );
47 
48 /*===========================================================================+
49  | PROCEDURE                                                                 |
50  |    set_rec_offset_flag		                		     |
51  |                                                                           |
52  | DESCRIPTION                                                               |
53  |    Sets the rec_offset_flag in ra_cust_trx_line_gl_dist for REC offsetting|
54  |    UNEARN/UNBILL rows if the flag has not been set already.  Procedure
55  |    has two parameters.  If called with customer_trx_id, it sets the flags
56  |    for that transaction.  If called by request_id, it sets the flags
57  |    for invoices targeted by CM transactions in that request_id group.
58  |    So, the request_id parameter is designed specifically for use by
59  |    autoinvoice.
60  |                                                                           |
61  | SCOPE - PUBLIC                                                           |
62  |    called from correct_rule_records_by_line and
63  |        from within ARP_CREDIT_MEMO_MODULE                                 |
64  |                                                                           |
65  | EXTERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
66  |    arp_util.debug                                                         |
67  |                                                                           |
68  | ARGUMENTS  : IN:                                                          |
69  | 		     p_customer_trx_id          			     |
70  |                   p_request_id                                     |
71  |              OUT:                                                         |
72  |									     |
73  |          IN/ OUT:							     |
74  |                    None						     |
75  |                                                                           |
76  |                                                                           |
77  | NOTES                                                                     |
78  |                                                                           |
79  | MODIFICATION HISTORY                                                      |
80  | 2-Aug-2002    Sahana    Bug2480898/Bug2493896: rec_offset_flag is not set |
81  |                         for older transactions causing rounding logic to  |
82  |                         corrupt UNEARN/UNBILL distributions               |
83  | 28-AUG-2002   M Raymond Bug 2535023 - Added request-id parameter so this
84  |                           could be safely called by arp_credit_memo_module
85  |                           for autoinvoice.
86  | 10-SEP-2002   M Raymond Corrected typo in request_id version.
87  | 28-MAY2003    H Yu      BUG#2750340 XLA Uptake
88  | 26-JUL-2006   M Raymond 5200647 - modified sql for performance impr.
89  | 27-OCT-2006   M Raymond 5611397 - Added hints
90  | 30-NOV-2007   M Raymond 6658402 - redesigned for performance issues
91  | 27-MAR-2008   M Raymond 6782405 - Added result parameter
92  |                            0 = no action needed, 1 = set rows, -1 = failure
93  | 14-MAY-2008   M Raymond 7039838 - FT tuning
94  +===========================================================================*/
95 PROCEDURE set_rec_offset_flag(p_customer_trx_id IN
96               ra_customer_trx.customer_trx_id%type,
97                p_request_id IN ra_customer_trx.request_id%type,
98                p_result     OUT NOCOPY NUMBER ) IS
99 
100   CURSOR inv_needing_rof(pp_request_id NUMBER) IS
101       SELECT DISTINCT inv_trx.customer_trx_id
102       FROM   RA_CUSTOMER_TRX  cm_trx,
103              RA_CUSTOMER_TRX  inv_trx,
104              RA_CUST_TRX_LINE_GL_DIST  inv_rec
105       WHERE  cm_trx.request_id = pp_request_id
106       AND    cm_trx.previous_customer_trx_id = inv_trx.customer_trx_id
107       AND    inv_trx.invoicing_rule_id IS NOT NULL
108       AND    inv_trx.customer_trx_id = inv_rec.customer_trx_id
109       AND    inv_rec.account_class = 'REC'
110       AND    inv_rec.account_set_flag = 'N'
111       AND    inv_rec.latest_rec_flag = 'Y'
112       AND NOT EXISTS
113             (SELECT /*+ NO_UNNEST NO_PUSH_SUBQ */
114                     'rof already set'
115              FROM   ra_cust_trx_line_gl_dist g2
116              WHERE  g2.customer_trx_id = inv_trx.customer_trx_id
117              AND    g2.account_set_flag = 'N'
118              AND    g2.account_class in ('UNEARN','UNBILL')
119              AND    g2.rec_offset_flag = 'Y');
120 
121     t_trx_id       l_line_id_type;
122     l_no_rof       NUMBER;
123     l_count        NUMBER;
124 BEGIN
125   IF PG_DEBUG in ('Y', 'C') THEN
126        arp_util.debug('arp_rounding.set_rec_offset_flag()+');
127   END IF;
128 
129        p_result := 0; -- no action needed
130 
131         IF (p_customer_trx_id is not NULL)
132         THEN
133 
134            IF (trx_for_rof is NULL OR
135                trx_for_rof <> p_customer_trx_id)
136            THEN
137 
138               /* We should only attempt to set ROF if
139                  a) target trx has been through Rev Rec
140                  b) target trx has no ROF flag for any one line
141               */
142 
143               SELECT count(*)
144               INTO   l_no_rof
145               FROM   ra_customer_trx_lines tl
146               WHERE  tl.customer_trx_id = p_customer_trx_id
147               AND    tl.line_type = 'LINE'
148               AND    tl.autorule_complete_flag IS NULL
149               AND    tl.accounting_rule_id IS NOT NULL
150               AND NOT EXISTS
151                     (SELECT /*+ NO_UNNEST NO_PUSH_SUBQ */
152                             'rof already set'
153                      FROM   ra_cust_trx_line_gl_dist g2
154                      WHERE  g2.customer_trx_id = tl.customer_trx_id
155                      AND    g2.account_set_flag = 'N'
156                      AND    g2.account_class in ('UNEARN','UNBILL')
157                      AND    g2.rec_offset_flag = 'Y');
158 
159               IF PG_DEBUG in ('Y', 'C') THEN
160                  arp_util.debug(' l_no_rof = ' || l_no_rof);
161               END IF;
162 
163               IF l_no_rof > 0
164               THEN
165 
166                  /* The UNNEST hint below was included as a defensive
167                     posture to an optimizer bug.  Without it, some
168                     10G databases do a full scan on gl_dist for the
169                     update line. */
170 
171                  /* 7039838 - added autoinv specific logic for
172                       FT tuning effort */
173                  IF g_autoinv
174                  THEN
175 
176                  UPDATE RA_CUST_TRX_LINE_GL_DIST
177                  SET    rec_offset_flag = 'Y'
178                  WHERE  cust_trx_line_gl_dist_id in
179                    (SELECT /*+ PUSH_SUBQ UNNEST
180                                index(tl RA_CUSTOMER_TRX_LINES_N4) */
181                            g.cust_trx_line_gl_dist_id
182                     FROM   ra_cust_trx_line_gl_dist g,
183                            ra_customer_trx_lines    tl,
184                            ra_cust_trx_line_gl_dist grec
185                     WHERE  tl.customer_trx_id = p_customer_trx_id
186                     AND    tl.request_id = g_autoinv_request_id
187                     AND    tl.accounting_rule_id is not null
188                     AND    tl.customer_trx_line_id = g.customer_trx_line_id
189                     AND    tl.line_type = 'LINE'
190                     AND    grec.customer_trx_id = tl.customer_trx_id
191                     AND    grec.account_class = 'REC'
192                     AND    grec.latest_rec_flag = 'Y'
193                     AND    grec.gl_date = g.gl_date
194                     AND    g.account_set_flag = 'N'
195                     AND    g.account_class in ('UNEARN','UNBILL')
196                     AND    g.revenue_adjustment_id is null
197                     AND    g.request_id is not null
198                     AND    sign(g.amount) = sign(tl.revenue_amount)
199                     AND    g.rec_offset_flag is null);
200 
201                  ELSE
202 
203                  UPDATE RA_CUST_TRX_LINE_GL_DIST
204                  SET    rec_offset_flag = 'Y'
205                  WHERE  cust_trx_line_gl_dist_id in
206                    (SELECT /*+ PUSH_SUBQ UNNEST */
207                            g.cust_trx_line_gl_dist_id
208                     FROM   ra_cust_trx_line_gl_dist g,
209                            ra_customer_trx_lines    tl,
210                            ra_cust_trx_line_gl_dist grec
211                     WHERE  tl.customer_trx_id = p_customer_trx_id
212                     AND    tl.accounting_rule_id is not null
213                     AND    tl.customer_trx_line_id = g.customer_trx_line_id
214                     AND    tl.line_type = 'LINE'
215                     AND    grec.customer_trx_id = tl.customer_trx_id
216                     AND    grec.account_class = 'REC'
217                     AND    grec.latest_rec_flag = 'Y'
218                     AND    grec.gl_date = g.gl_date
219                     AND    g.account_set_flag = 'N'
220                     AND    g.account_class in ('UNEARN','UNBILL')
221                     AND    g.revenue_adjustment_id is null
222                     AND    g.request_id is not null
223                     AND    sign(g.amount) = sign(tl.revenue_amount)
224                     AND    g.rec_offset_flag is null);
225 
226                  END IF; -- end g_autoinv
227 
228                     l_count := SQL%ROWCOUNT;
229 
230                   IF PG_DEBUG in ('Y', 'C') THEN
231                      arp_util.debug('   updated ' || l_count ||
232                             ' rec_offset rows.');
233                   END IF;
234 
235                     /* indicate if rows were set or not */
236                     IF l_count > 0
237                     THEN
238                        p_result := 1; -- rows were set
239                     ELSE
240                        p_result := -1; -- no rows were set
241                     END IF;
242 
243               END IF;
244 
245                  /* Now set trx_for_rof so this does not execute again
246                     for this transaction within this session. */
247                  trx_for_rof := p_customer_trx_id;
248            END IF;
249 
250         ELSE
251           /* Request ID - specifically for CMs via autoinvoice */
252           IF (rqid_for_rof is NULL or
253               rqid_for_rof <> p_request_id)
254           THEN
255 
256              /* 6658402 - Executing a bulk fetch, then a
257                   forall update to improve performance */
258              OPEN inv_needing_rof(p_request_id);
259  	     FETCH inv_needing_rof BULK COLLECT INTO
260                              t_trx_id;
261 
262              l_no_rof := inv_needing_rof%ROWCOUNT;
263 
264              CLOSE inv_needing_rof;
265 
266              IF l_no_rof > 0
267              THEN
268                FORALL i IN t_trx_id.FIRST .. t_trx_id.LAST
269                UPDATE RA_CUST_TRX_LINE_GL_DIST G
270                  SET    rec_offset_flag = 'Y'
271                  WHERE G.cust_trx_line_gl_dist_id in
272                    (SELECT /*+ PUSH_SUBQ ORDERED UNNEST */
273                            inv_g.cust_trx_line_gl_dist_id
274                     FROM   ra_customer_trx_lines    inv_l,
275                            ra_cust_trx_line_gl_dist inv_g,
276                            ra_cust_trx_line_gl_dist inv_grec
277                     WHERE  inv_l.customer_trx_id = t_trx_id(i)
278                     AND    inv_l.accounting_rule_id is not null
279                     AND    inv_l.customer_trx_line_id =
280                               inv_g.customer_trx_line_id
281                     AND    inv_l.line_type = 'LINE'
282                     AND    inv_grec.customer_trx_id = inv_l.customer_trx_id
283                     AND    inv_grec.account_class = 'REC'
284                     AND    inv_grec.latest_rec_flag = 'Y'
285                     AND    inv_grec.gl_date = inv_g.gl_date
286                     AND    inv_g.account_set_flag = 'N'
287                     AND    inv_g.account_class in ('UNEARN','UNBILL')
288                     AND    inv_g.revenue_adjustment_id is null
289                     AND    inv_g.request_id is not null
290                     AND    sign(inv_g.amount) = sign(inv_l.revenue_amount)
291                     AND    inv_g.rec_offset_flag is null);
292 
293               l_count := SQL%ROWCOUNT;
294 
295               IF PG_DEBUG in ('Y', 'C') THEN
296                  arp_util.debug('   updated ' || l_count || ' rec_offset rows.');
297               END IF;
298               IF l_count > 0
299               THEN
300                   /* we updated some.  Technically, this does not mean
301                      we are out of the woods, but we'll assume it set them */
302                   p_result := 1;
303               ELSE
304                   /* no rows updated when some needed it */
305                   p_result := -1;
306               END IF;
307 
308               rqid_for_rof := p_request_id;
309              END IF;
310           END IF;
311         END IF;
312 
313   IF PG_DEBUG in ('Y', 'C') THEN
314        arp_util.debug('arp_rounding.set_rec_offset_flag()-');
315   END IF;
316 EXCEPTION
317 WHEN OTHERS THEN
318    arp_util.debug('EXCEPTION:  arp_process_dist.set_rec_offset_flag()');
319    RAISE;
320 END;
321 
322 /*===========================================================================+
323  | PRIVATE PROCEDURE                                                                 |
324  |    true_lines_by_gl_date		                		     |
325  |                                                                           |
326  | DESCRIPTION                                                               |
327  |    This procedure tests each gl_date for a transaction line to verify
328  |    that the gl_dist rows sum to zero on that date.  If they do not,
329  |    we update a dist row on that date for the delta amount and/or percent.
330  |    The row chosen for update is the one with the max gl_dist_id on that
331  |    date with an amount that has the same sign as the extended_amount
332  |    of the line.
333  |
334  |    This means that we will generally update REV lines for both invoices
335  |    and credit memos - unless there is a more recent adjustment on the
336  |    line, which will push us to choose the latest adjustment distribution.
337  |                                                                           |
338  |    As a bonus, we now also check RAM distributions separately from
339  |    conventional distributions and round them (by line_id, gl_date, and
340  |    revenue_adjustment_id) if they need it.
341  |
342  | SCOPE - PRIVATE                                                           |
343  |    called from correct_rule_records_by_line
344  |                                                                           |
345  | EXTERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
346  |    arp_util.debug                                                         |
347  |                                                                           |
348  | ARGUMENTS  : IN:                                                          |
349  | 		     p_customer_trx_id          			     |
350  |              OUT:                                                         |
351  |									     |
352  |          IN/ OUT:							     |
353  |                    None						     |
354  |                                                                           |
355  |                                                                           |
356  | NOTES                                                                     |
357  |                                                                           |
358  | MODIFICATION HISTORY                                                      |
359  | 05-SEP-2002   M RAYMOND   Bug 2535023 - Created
360  | 09-SEP-2002   M RAYMOND   Bug 2543675 - Excluded non-rule trx from
361  |                                         being processed.
362  | 13-SEP-2002   M RAYMOND   Bug 2543675 - Process RAM dists to make sure
363  |                                         that they balance, too.
364  |
365  +===========================================================================*/
366 PROCEDURE true_lines_by_gl_date(p_customer_trx_id IN
367               ra_customer_trx.customer_trx_id%type) IS
368 
369   /* Cursor for TRUing by gl_date
370      Detects GL_DATES that do not sum to zero.
371      This is usually due to behavior of older
372      autoaccounting or shortcomings in trx workbench
373      calculations.  It should not pick up non-rule trx
374      or CMs on non-rule trx.*/
375   CURSOR true_rows_by_date(p_trx_id NUMBER) IS
376      select g.customer_trx_line_id, g.gl_date,
377             sum(g.amount), sum(g.acctd_amount), sum(g.percent),
378             nvl(revenue_adjustment_id, -99) revenue_adjustment_id
379      from   ra_cust_trx_line_gl_dist g,
380             ra_customer_trx h,
381             ra_customer_trx prev_h
382      where  h.customer_trx_id = p_trx_id
383      and    h.previous_customer_trx_id = prev_h.customer_trx_id (+)
384      and    nvl(h.invoicing_rule_id, prev_h.invoicing_rule_id) is not null
385      and    g.customer_trx_id = h.customer_trx_id
386      and    g.account_class in ('REV','UNEARN','UNBILL')
387      and    g.account_set_flag = 'N'
388      and    g.rec_offset_flag is null
389      and    g.posting_control_id = -3
390      group by g.customer_trx_line_id, g.gl_date, nvl(g.revenue_adjustment_id, -99)
391      having sum(amount) <> 0 or sum(acctd_amount) <> 0 or sum(percent) <> 0;
392 
393   CURSOR true_rows_by_date_gt IS
394      select g.customer_trx_line_id, g.gl_date,
395             sum(g.amount), sum(g.acctd_amount), sum(g.percent),
396             nvl(g.revenue_adjustment_id, -99) revenue_adjustment_id
397      from   ra_cust_trx_line_gl_dist g,
398             ar_line_rev_adj_gt gt,
399             ra_customer_trx h,
400             ra_customer_trx prev_h
401      where  h.customer_trx_id = g.customer_trx_id
402      and    h.previous_customer_trx_id = prev_h.customer_trx_id (+)
403      and    nvl(h.invoicing_rule_id, prev_h.invoicing_rule_id) is not null
404      and    g.customer_trx_line_id = gt.customer_trx_line_id
405      and    g.account_class in ('REV','UNEARN','UNBILL')
406      and    g.account_set_flag = 'N'
407      and    g.rec_offset_flag is null
408      and    g.posting_control_id = -3
409      group by g.customer_trx_line_id, g.gl_date, nvl(g.revenue_adjustment_id, -99)
410      having sum(g.amount) <> 0 or sum(g.acctd_amount) <> 0 or sum(g.percent) <> 0;
411 
412 
413   /* Tables for truing lines */
414   t_true_line_id  l_line_id_type;
415   t_true_gl_date  l_date_type;
416   t_true_amount   l_amount_type;
417   t_true_acctd    l_amount_type;
418   t_true_percent  l_percent_type;
419   t_true_ram_id   l_line_id_type;
420 
421   l_rows_needing_truing NUMBER;
422 
423 BEGIN
424      arp_util.debug('arp_rounding.true_lines_by_gl_date()+');
425 
426      IF (p_customer_trx_id IS NOT NULL)
427      THEN
428         /* True the rows (if required) */
429         OPEN true_rows_by_date(P_CUSTOMER_TRX_ID);
430            FETCH true_rows_by_date BULK COLLECT INTO
431                              t_true_line_id,
432                              t_true_gl_date,
433                              t_true_amount,
434                              t_true_acctd,
435                              t_true_percent,
436                              t_true_ram_id;
437 
438         l_rows_needing_truing := true_rows_by_date%ROWCOUNT;
439 
440         CLOSE true_rows_by_date;
441      ELSE
442         /* True the rows (if required) */
443         OPEN true_rows_by_date_gt;
444            FETCH true_rows_by_date_gt BULK COLLECT INTO
445                              t_true_line_id,
446                              t_true_gl_date,
447                              t_true_amount,
448                              t_true_acctd,
449                              t_true_percent,
450                              t_true_ram_id;
451 
452         l_rows_needing_truing := true_rows_by_date_gt%ROWCOUNT;
453 
454         CLOSE true_rows_by_date_gt;
455 
456      END IF;
457 
458      /* Now update all the rows that require it */
459 
460      arp_standard.debug('Rows that need truing: ' || l_rows_needing_truing);
461 
462      IF (l_rows_needing_truing > 0) THEN
463 
464         FORALL i IN t_true_line_id.FIRST .. t_true_line_id.LAST
465             UPDATE ra_cust_trx_line_gl_dist g
466             SET    amount = amount - t_true_amount(i),
467                    percent = percent - t_true_percent(i),
468                    acctd_amount = acctd_amount - t_true_acctd(i),
469                    last_updated_by = arp_global.last_updated_by,
470                    last_update_date = sysdate
471             WHERE  cust_trx_line_gl_dist_id in (
472               /* SELECT GL_DIST_ID FOR EACH DATE THAT
473                  REQUIRES TRUING */
474               select MAX(g.cust_trx_line_gl_dist_id)
475               from   ra_cust_trx_line_gl_dist g,
476                      ra_customer_trx_lines    tl
477               where  g.customer_trx_line_id = t_true_line_id(i)
478               and    g.gl_date              = t_true_gl_date(i)
479               and    g.customer_trx_line_id = tl.customer_trx_line_id
480               and    sign(g.amount) = sign(tl.revenue_amount)
481               and    g.account_set_flag = 'N'
482               and    g.rec_offset_flag is null
483               and    nvl(g.revenue_adjustment_id, -99) = t_true_ram_id(i)
484               and    g.posting_control_id = -3
485               /* END OF GL_DIST BY DATE SELECT */
486               );
487 
488        IF (l_rows_needing_truing <> SQL%ROWCOUNT) THEN
489 
490           /* There was a problem and we did not update the correct number
491              of rows.  Display the rows requiring update and indicate if they were
492              updated. */
493 
494           arp_standard.debug('Mismatch between lines found and lines updated for truing (see below)');
495 
496           arp_standard.debug('Rows targeted for truing:');
497 
498           FOR err in t_true_line_id.FIRST .. t_true_line_id.LAST LOOP
499 
500               arp_standard.debug( t_true_line_id(err) || '  ' ||
501                                        t_true_gl_date(err) || '  ' ||
502                                        t_true_amount(err) || ' ' ||
503                                        t_true_acctd(err) || ' ' ||
504                                        t_true_percent(err) || '   ' ||
505                                        SQL%BULK_ROWCOUNT(err));
506 
507           END LOOP;
508 
509           /* While I am concerned if we were unable to find a row for truing,
510              I don't think it is grounds for failing the process because it
511              could be some unforeseen situation.  So, I let it fall into
512              the standard rounding code where we will make sure the transaction
513              line balances.  */
514 
515        END IF;
516 
517      END IF;
518 
519      arp_util.debug('arp_rounding.true_lines_by_gl_date()-');
520 EXCEPTION
521 WHEN OTHERS THEN
522    arp_util.debug('EXCEPTION:  arp_rounding.true_lines_by_gl_date()');
523    RAISE;
524 END;
525 
526 /*===========================================================================+
527  | PRIVATE PROCEDURE                                                        |
528  |    correct_suspense		                		     |
529  |                                                                           |
530  | DESCRIPTION                                                               |
531  |    This procedure tweaks SUSPENSE lines in cases where line-level
532  |    rounding and autoinvoice clearing are both enabled.  This same issue
533  |    is handled properly for header-level rounding by a previous bug.
534  |                                                                           |
535  |    Technically speaking, this code only actually processes (corrects)
536  |    when the transaction has rules.  Non-rule transactions already round
537  |    arbitrarily to a single REV or SUSPENSE distribution.
538  |
539  | SCOPE - PRIVATE                                                           |
540  |    called from do_line_level_rounding
541  |                                                                           |
542  | EXTERNAL PROCEDURES/FUNCTIONS ACCESSED                                   |
543  |    arp_util.debug                                                         |
544  |                                                                           |
545  | ARGUMENTS  : IN:                                                          |
546  | 		     p_customer_trx_id          			     |
547  |                   p_request_id                                     |
548  |              OUT:                                                         |
549  |          IN/ OUT:							     |
550  |                    None						     |
551  |                                                                           |
552  |                                                                           |
553  | NOTES                                                                     |
554  |                                                                           |
555  | MODIFICATION HISTORY                                                      |
556  | 29-APR-04     M Raymond Created
557  | 26-MAY-04     M Raymond 3651898 - removed error handling condition
558  |                         as it was raising an error unnecessarily
559  | 01-JUN-04     M Raymond Converted from FUNCTION to PROCEDURE
560  +===========================================================================*/
561 PROCEDURE correct_suspense(p_customer_trx_id IN
562               ra_customer_trx.customer_trx_id%type) IS
563 
564    l_acctd_correction ra_cust_trx_line_gl_dist.acctd_amount%type;
565    l_rows  NUMBER;
566 BEGIN
567        arp_util.debug('arp_rounding.correct_suspense()+');
568 
569         IF (p_customer_trx_id is not NULL)
570         THEN
571 
572            l_acctd_correction :=
573               get_dist_round_acctd_amount(p_customer_trx_id);
574 
575            IF (l_acctd_correction <> 0)
576            THEN
577                  UPDATE RA_CUST_TRX_LINE_GL_DIST
578                  SET    acctd_amount = acctd_amount + l_acctd_correction
579                  WHERE  cust_trx_line_gl_dist_id in
580                    (SELECT MAX(g.cust_trx_line_gl_dist_id)
581                     FROM   ra_cust_trx_line_gl_dist g
582                     WHERE  g.account_class = 'SUSPENSE'
583                     AND    g.account_set_flag = 'N'
584                     AND    g.customer_trx_id = p_customer_trx_id
585                     AND    g.posting_control_id = -3
586                     AND    g.acctd_amount = (
587                        SELECT MAX(g2.acctd_amount)
588                        FROM   ra_cust_trx_line_gl_dist g2
589                        WHERE  g2.customer_trx_id = p_customer_trx_id
590                        AND    g2.account_class = 'SUSPENSE'
591                        AND    g2.account_set_flag = 'N'
592                        AND    g2.posting_control_id = -3));
593 
594                  l_rows := SQL%ROWCOUNT;
595                  arp_util.debug('   updated ' || l_rows
596                                                || ' suspense rows.');
597 
598            ELSE
599                  arp_util.debug('   no suspense correction required');
600            END IF;
601 
602         END IF;
603 /***********************************************
604  * MRC Processing Bug 4018317 Added the call   *
605  * required for new procedure correct_suspense *
606  **********************************************/
607   IF PG_DEBUG in ('Y', 'C') THEN
608      arp_standard.debug('doing rounding for MRC if necessary');
609   END IF;
610   ar_mrc_engine2.mrc_correct_rounding(
611                    'CORRECT_SUSPENSE',
612                    NULL, /*P_REQUEST_ID */
613                    P_CUSTOMER_TRX_ID,
614                    NULL,    /* customer trx line id */
615                    NULL, /*p_trx_class_to_process */
616          	   NULL,   /* concat_segs */
617                    NULL,  /* balanced round_ccid */
618                    NULL, /*p_check_rules_flag*/
619                    NULL /*p_period_set_name */
620                   );
621   IF PG_DEBUG in ('Y', 'C') THEN
622    arp_util.debug('arp_rounding.correct_suspense-');
623   END IF;
624 EXCEPTION
625 WHEN OTHERS THEN
626    arp_util.debug('EXCEPTION:  arp_process_dist.correct_suspense()');
627 END;
628 
629 /*-------------------------------------------------------------------------+
630  | PRIVATE FUNCTION                                                        |
631  |   do_setup()                                                            |
632  |                                                                         |
633  | DESCRIPTION                                                             |
634  |   This function checks the parameters for validity and sets some        |
635  |   default values.                                                       |
636  |                                                                         |
637  | REQUIRES                                                                |
638  |   All IN parameters.                                                    |
639  |                                                                         |
640  | RETURNS                                                                 |
641  |   TRUE   if no errors occur and all of the parameters are valid.        |
642  |   FALSE  otherwise.                                                     |
643  |                                                                         |
644  | NOTES                                                                   |
645  |   The function does the following parameter validations:                |
646  |                                                                         |
647  |   1) Either the REQUEST_ID,  CUSTOMER_TRX_ID or CUSTOMER_TRX_LINE_ID    |
648  |      parameters must be not null.                                       |
649  |                                                                         |
650  |   2) If REQUEST_ID is specified, CUSTOMER_TRX_ID and                    |
651  |      CUSTOMER_TRX_LINE_ID must be null.                                 |
652  |                                                                         |
653  |   3) If CUSTOMER_TRX_LINE_ID is specified, CUSTOMER_TRX_ID must be      |
654  |      specified.                                                         |
655  |                                                                         |
656  |   4) TRX_CLASS_TO_PROCESS must be either null, REGULAR_CM, INV or ALL.  |
657  |                                                                         |
658  |   5) CHECK_RULES_FLAG must be either null, Y or N.                      |
659  |                                                                         |
660  |   6) P_TRX_HEADER_LEVEL_ROUNDING must be either null, Y or N.           |
661  |                                                                         |
662  |   7) P_ACTIVITY_FLAG must be either null, Y or N.                       |
663  |                                                                         |
664  |   8) P_TRX_HEADER_LEVEL_ROUNDING is Y then either the REQUEST_ID or     |
665  |      CUSTOMER_TRX_ID parameters must be not null.                       |
666  |                                                                         |
667  | EXAMPLE                                                                 |
668  |                                                                         |
669  | MODIFICATION HISTORY                                                    |
670  |                                                                         |
671  +-------------------------------------------------------------------------*/
672 
673 
674 FUNCTION do_setup( P_REQUEST_ID                    IN NUMBER,
675                    P_CUSTOMER_TRX_ID               IN NUMBER,
676                    P_CUSTOMER_TRX_LINE_ID          IN NUMBER,
677                    P_BASE_PRECISION                IN NUMBER,
678                    P_BASE_MIN_ACCOUNTABLE_UNIT     IN VARCHAR2,
679                    P_TRX_CLASS_TO_PROCESS          IN VARCHAR2,
680                    P_CHECK_RULES_FLAG              IN VARCHAR2,
681                    P_DEBUG_MODE                    IN VARCHAR2,
682                    BASE_PRECISION                  OUT NOCOPY NUMBER,
683                    BASE_MIN_ACCOUNTABLE_UNIT       OUT NOCOPY NUMBER,
684                    TRX_CLASS_TO_PROCESS            OUT NOCOPY VARCHAR2,
685                    CHECK_RULES_FLAG                OUT NOCOPY VARCHAR2,
686                    PERIOD_SET_NAME                 OUT NOCOPY VARCHAR2,
687                    P_ROWS_PROCESSED                OUT NOCOPY NUMBER,
688                    P_ERROR_MESSAGE                 OUT NOCOPY VARCHAR2,
689                    P_TRX_HEADER_LEVEL_ROUNDING     IN  VARCHAR2,
690                    P_ACTIVITY_FLAG                 IN  VARCHAR2,
691                    ACTIVITY_FLAG                   OUT NOCOPY VARCHAR2,
692                    TRX_HEADER_ROUND_CCID           OUT NOCOPY NUMBER
693                  ) RETURN NUMBER IS
694 
695 BEGIN
696 
697  /*-------------------------------+
698   |  Enable debug mode if desired |
699   +-------------------------------*/
700 
701  IF    (p_debug_mode = 'Y')
702  THEN
703        arp_standard.enable_debug;
704  ELSE  IF (p_debug_mode = 'N')
705        THEN
706            arp_standard.disable_debug;
707        END IF;
708  END IF;
709 
710  IF PG_DEBUG in ('Y', 'C') THEN
711     arp_standard.debug('  arp_rounding.do_setup()+ ' ||
712                     TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
713  END IF;
714 
715   /*----------------------+
716     | Validate parameters |
717     +---------------------*/
718    IF PG_DEBUG in ('Y', 'C') THEN
719       arp_standard.debug('Request_id: ' || p_request_id ||
720                      ' ctid: '|| p_customer_trx_id ||'  ctlid: '||
721                      p_customer_trx_line_id || '  class: ' ||
722                      trx_class_to_process || '  Rules: '||
723                      check_rules_flag);
724    END IF;
725 
726 
727   /*---------------------------------------------------+
728    |  6) P_TRX_HEADER_LEVEL_ROUNDING must be Y or N.   |
729    +---------------------------------------------------*/
730 
731   if   (
732           p_trx_header_level_rounding not in ('Y', 'N')
733        )
734   then
735        p_error_message := 'arp_rounding - ' ||
736        arp_standard.fnd_message('AR_CUST_INVALID_PARAMETER', 'PARAMETER', p_trx_header_level_rounding, 'P_TRX_HEADER_LEVEL_ROUNDING');
737 
738        return(iFALSE);
739   end if;
740 
741   /*-------------------------------------------------------------+
742    |  1) Either the REQUEST_ID,  CUSTOMER_TRX_ID or              |
743    |     CUSTOMER_TRX_LINE_ID parameters must be not null.       |
744    |                                                             |
745    |  2) If REQUEST_ID is specified, CUSTOMER_TRX_ID and         |
746    |     CUSTOMER_TRX_LINE_ID must be null.                      |
747    |                                                             |
748    |  3) If CUSTOMER_TRX_LINE_ID is specified, CUSTOMER_TRX_ID   |
749    |     must be specified.                                      |
750    |                                                             |
751    |  8) If p_trx_header_level_rounding  = Y then either the     |
752    |     REQUEST_ID or CUSTOMER_TRX_ID parameters must be        |
753    |     not null.                                               |
754    +------------------------------------------------------------*/
755 
756  IF   (
757         (
758           p_request_id           IS NULL AND
759           p_customer_trx_id      IS NULL AND
760           p_customer_trx_line_id IS NULL
761         )
762        OR
763         (
764           p_request_id       IS NOT NULL AND
765           (p_customer_trx_id IS NOT NULL OR p_customer_trx_line_id IS NOT NULL)
766         )
767        OR
768         (
769           p_customer_trx_line_id is not null AND
770           p_customer_trx_id is null
771         )
772        OR
773         ( p_trx_header_level_rounding = 'Y' AND
774           p_request_id is null              AND
775           p_customer_trx_id is null
776         )
777        )
778   THEN
779        p_error_message := 'arp_rounding - ' ||
780                arp_standard.fnd_message(arp_standard.MD_MSG_NUMBER,
781                                        'AR-PLCRE-PARAM-ID') || ' - ' ||
782                           arp_standard.fnd_message('AR-PLCRE-PARAM-ID');
783        RETURN( iFALSE );
784 
785   END IF;
786 
787 
788   /*------------------------------------------+
789    |  4) TRX_CLASS_TO_PROCESS must be either: |
790    |     null, REGULAR_CM, INV or ALL.        |
791    +------------------------------------------*/
792 
793   IF (
794       p_trx_class_to_process IS NOT NULL AND
795       p_trx_class_to_process NOT IN ('REGULAR_CM', 'INV', 'ALL')
796      )
797   THEN
798       p_error_message := 'arp_rounding - ' ||
799            arp_standard.fnd_message(arp_standard.MD_MSG_NUMBER,
800                                     'AR-PLCRE-PARAM-CLASS') || ' - ' ||
801                           arp_standard.fnd_message('AR-PLCRE-PARAM-CLASS');
802       RETURN( iFALSE );
803   ELSE
804       trx_class_to_process := p_trx_class_to_process;
805   END IF;
806 
807 
808   /*---------------------------------------------------+
809    |  5) CHECK_RULES_FLAG must be either null, Y or N. |
810    +---------------------------------------------------*/
811 
812   IF (
813       p_check_rules_flag IS NOT NULL AND
814       p_check_rules_flag NOT IN ('Y', 'N')
815      )
816   THEN
817       p_error_message := 'arp_rounding - ' ||
818             arp_standard.fnd_message(arp_standard.MD_MSG_NUMBER,
819                                  'AR-PLCRE-PARAM-RULES') || ' - ' ||
820                           arp_standard.fnd_message('AR-PLCRE-PARAM-RULES');
821       RETURN( iFALSE );
822   ELSE
823        check_rules_flag := p_check_rules_flag;
824   END IF;
825 
826   /*---------------------------------------------------+
827    |  7) P_ACTIVITY_FLAG must be either null, Y or N. |
828    +---------------------------------------------------*/
829 /* bug 912501 : Added 'G' for the possible values of p_activity_flag */
830   if   (
831           p_activity_flag is not null AND
832           p_activity_flag not in ('Y', 'N','G')
833        )
834   then
835        p_error_message := 'arp_rounding - ' ||
836        arp_standard.fnd_message('AR_CUST_INVALID_PARAMETER', 'PARAMETER', p_activity_flag, 'PARAMETER', 'P_ACTIVITY_FLAG');
837 
838        return(iFALSE);
839   else
840        activity_flag := p_activity_flag;
841   end if;
842 
843    /*--------------------+
844     | Set default values |
845     +--------------------*/
846 
847   p_rows_processed := 0;
848 
849   IF (p_trx_class_to_process IS NULL)
850   THEN
851       trx_class_to_process := 'ALL';
852   END IF;
853 
854   IF (p_check_rules_flag IS NULL)
855   THEN
856       check_rules_flag := 'N';
857   END IF;
858 
859   if    (p_activity_flag is null)
860   then  activity_flag := 'N';
861   end if;
862 
863   if (
864         (p_base_precision is null and p_base_min_accountable_unit is null)
865       OR
866       ( p_check_rules_flag = 'Y' )
867      )
868   THEN
869 
870      SELECT
871             precision,
872             minimum_accountable_unit,
873             period_set_name
874      INTO
875             base_precision,
876             base_min_accountable_unit,
877             period_set_name
878      FROM
879             fnd_currencies       f,
880             gl_sets_of_books     b,
881             ar_system_parameters p
882      WHERE
883             p.set_of_books_id = b.set_of_books_id
884      AND    f.currency_code   = b.currency_code;
885 
886   ELSE
887 
888       base_precision            := p_base_precision;
889       base_min_accountable_unit := p_base_min_accountable_unit;
890   end if;
891 
892   trx_header_round_ccid :=
893          arp_global.sysparam.trx_header_round_ccid;
894 
895    /*------------------------------------------+
896     | Set default values                       |
897     | If p_trx_header_level_rounding  = Y then |
898     | trx_header_round_ccid should be not null |
899     +------------------------------------------*/
900 
901   if   (
902           p_trx_header_level_rounding = 'Y' AND
903           (trx_header_round_ccid is null  OR
904            trx_header_round_ccid = -1)
905        )
906   then
907        FND_MESSAGE.set_name('AR','AR-PLCRE-THLR-CCID');
908        p_error_message := 'arp_rounding - ' || fnd_message.get;
909        return(iFALSE);
910   end if;
911 
912   IF PG_DEBUG in ('Y', 'C') THEN
913      arp_standard.debug( 'arp_rounding.do_setup()- ' ||
914                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
915   END IF;
916 
917   RETURN( iTRUE );
918 
919 END do_setup;
920 
921 /*-------------------------------------------------------------------------+
922  | PRIVATE FUNCTION                                                        |
923  |   insert_round_records()                                                |
924  |                                                                         |
925  | DESCRIPTION                                                             |
926  |   This function inserts one record of account_class ROUND into the      |
927  |   ra_cust_trx_line_gl_dist table.                                       |
928  |                                                                         |
929  |   If the ROUND record already exist for a transaction then it is not    |
930  |   inserted again. Like the REC record there will be only 1 (2 in case of|
931  |   transaction with rule) ROUND record for each transaction.             |
932  |   The ROUND record is copied from the REC record of the invoice         |
933  |                                                                         |
934  |   Some of the column values for the ROUND record  are as follows:       |
935  |                                                                         |
936  |   customer_trx_line_id = NULL                                           |
937  |   gl_date              = receivable gl_date                             |
938  |   latest_rec_flag      = NULL                                           |
939  |   account_set_flag     = receivable account_set_flag                    |
940  |                                                                         |
941  | REQUIRES                                                                |
942  |                                                                         |
943  | RETURNS                                                                 |
944  |   TRUE  if no errors occur                                              |
945  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
946  |                                                                         |
947  | NOTES                                                                   |
948  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
949  |                                                                         |
950  | EXAMPLE                                                                 |
951  |                                                                         |
952  | MODIFICATION HISTORY                                                    |
953  | 13-Aug-2002    Debbie Jancis    Modified for mrc trigger replacement    |
954  |                                 added calls for insert into             |
955  |                                 ra_cust_trx_line_gl_dist                |
956  | 24-SEP-2002    M.Ryzhikova      Modified for mrc trigger replacement.   |
957  | 01-OCT-2003    M Raymond        Bug 3067588 - made this function public
958  +-------------------------------------------------------------------------*/
959 
960 FUNCTION insert_round_records( P_REQUEST_ID IN NUMBER,
961                                P_CUSTOMER_TRX_ID       IN NUMBER,
962                                P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
963                                P_ERROR_MESSAGE            OUT NOCOPY VARCHAR2,
964                                P_BASE_PRECISION        IN NUMBER,
965                                P_BASE_MAU              IN NUMBER,
966                                P_TRX_CLASS_TO_PROCESS  IN VARCHAR2,
967                                P_TRX_HEADER_ROUND_CCID IN NUMBER)
968 RETURN NUMBER IS
969 
970  rows  NUMBER;
971 
972  l_gl_dist_key_value_list gl_ca_utility_pkg.r_key_value_arr;   /* mrc */
973  --BUG#2750340
974  l_xla_ev_rec             ARP_XLA_EVENTS.XLA_EVENTS_TYPE;
975 
976 begin
977 
978   rows := 0;
979   IF PG_DEBUG in ('Y', 'C') THEN
980      arp_standard.debug('arp_rounding.insert_round_record()+ ' ||
981                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
982   END IF;
983 
984 if (p_request_id is not null )
985 then
986    IF PG_DEBUG in ('Y', 'C') THEN
987       arp_standard.debug('p_request_id is not null ....' || to_char(p_request_id));
988    END IF;
989 
990 insert into ra_cust_trx_line_gl_dist
991  (POST_REQUEST_ID           ,
992   POSTING_CONTROL_ID        ,
993   ACCOUNT_CLASS             ,
994   RA_POST_LOOP_NUMBER       ,
995   CUSTOMER_TRX_ID           ,
996   ACCOUNT_SET_FLAG          ,
997   ACCTD_AMOUNT              ,
998   USSGL_TRANSACTION_CODE    ,
999   USSGL_TRANSACTION_CODE_CONTEXT  ,
1000   ATTRIBUTE11                     ,
1001   ATTRIBUTE12                     ,
1002   ATTRIBUTE13                     ,
1003   ATTRIBUTE14                     ,
1004   ATTRIBUTE15                     ,
1005   LATEST_REC_FLAG                 ,
1006   ORG_ID                          ,
1007   CUST_TRX_LINE_GL_DIST_ID        ,
1008   CUSTOMER_TRX_LINE_ID            ,
1009   CODE_COMBINATION_ID             ,
1010   SET_OF_BOOKS_ID                 ,
1011   LAST_UPDATE_DATE                ,
1012   LAST_UPDATED_BY                 ,
1013   CREATION_DATE                   ,
1014   CREATED_BY                      ,
1015   LAST_UPDATE_LOGIN               ,
1016   PERCENT                         ,
1017   AMOUNT                          ,
1018   GL_DATE                         ,
1019   GL_POSTED_DATE                  ,
1020   CUST_TRX_LINE_SALESREP_ID       ,
1021   COMMENTS                        ,
1022   ATTRIBUTE_CATEGORY              ,
1023   ATTRIBUTE1                      ,
1024   ATTRIBUTE2                      ,
1025   ATTRIBUTE3                      ,
1026   ATTRIBUTE4                      ,
1027   ATTRIBUTE5                      ,
1028   ATTRIBUTE6                      ,
1029   ATTRIBUTE7                      ,
1030   ATTRIBUTE8                      ,
1031   ATTRIBUTE9                      ,
1032   ATTRIBUTE10                     ,
1033   REQUEST_ID                      ,
1034   PROGRAM_APPLICATION_ID          ,
1035   PROGRAM_ID                      ,
1036   PROGRAM_UPDATE_DATE             ,
1037   CONCATENATED_SEGMENTS           ,
1038   ORIGINAL_GL_DATE                )
1039 select
1040 POST_REQUEST_ID,
1041 -3,
1042 'ROUND',
1043 RA_POST_LOOP_NUMBER,
1044 CUSTOMER_TRX_ID,
1045 ACCOUNT_SET_FLAG,
1046 NULL,  /* acctd_amount */
1047 USSGL_TRANSACTION_CODE,
1048 USSGL_TRANSACTION_CODE_CONTEXT,
1049 ATTRIBUTE11,
1050 ATTRIBUTE12,
1051 ATTRIBUTE13,
1052 ATTRIBUTE14,
1053 ATTRIBUTE15,
1054 NULL,      /* LATEST_REC_FLAG */
1055 ORG_ID,
1056 RA_CUST_TRX_LINE_GL_DIST_s.nextval,
1057 CUSTOMER_TRX_LINE_ID,
1058 P_TRX_HEADER_ROUND_CCID,  /* CODE_COMBINATION_ID */
1059 SET_OF_BOOKS_ID,
1060 SYSDATE,
1061 arp_global.last_updated_by,
1062 SYSDATE,
1063 arp_global.created_by,
1064 arp_global.last_update_login,
1065 PERCENT,
1066 NULL,  /* AMOUNT */
1067 GL_DATE,
1068 GL_POSTED_DATE,
1069 CUST_TRX_LINE_SALESREP_ID,
1070 COMMENTS,
1071 ATTRIBUTE_CATEGORY,
1072 ATTRIBUTE1,
1073 ATTRIBUTE2,
1074 ATTRIBUTE3,
1075 ATTRIBUTE4,
1076 ATTRIBUTE5,
1077 ATTRIBUTE6,
1078 ATTRIBUTE7,
1079 ATTRIBUTE8,
1080 ATTRIBUTE9,
1081 ATTRIBUTE10,
1082 arp_global.request_id,
1083 arp_global.program_application_id,
1084 arp_global.program_id,
1085 arp_global.program_update_date,
1086 CONCATENATED_SEGMENTS,
1087 ORIGINAL_GL_DATE
1088 from ra_cust_trx_line_gl_dist rec
1089 where account_class = 'REC'
1090 and   latest_rec_flag = 'Y'
1091 and   gl_posted_date is null
1092 and   rec.request_id = p_request_id
1093 /* bug3311759 : Removed
1094 and   not exists ( select 1
1095                    from   ra_cust_trx_line_gl_dist dist2
1096                    where  dist2.customer_trx_id = rec.customer_trx_id
1097                    and    dist2.account_class in ('UNEARN','UNBILL')
1098                    and    dist2.account_set_flag = 'N')
1099 */
1100 and   not exists ( select 1
1101                    from   ra_cust_trx_line_gl_dist dist2
1102                    where  dist2.customer_trx_id = rec.customer_trx_id
1103                    and    dist2.account_class = 'ROUND'
1104                    and    dist2.account_set_flag = rec.account_set_flag);
1105 
1106     rows := SQL%ROWCOUNT;
1107 
1108     IF (rows > 0) THEN
1109        IF PG_DEBUG in ('Y', 'C') THEN
1110           arp_standard.debug('calling mrc engine for insertion of gl dist data');
1111        END IF;
1112        ar_mrc_engine.mrc_bulk_process(
1113                     p_request_id   => p_request_id,
1114                     p_table_name   => 'GL_DIST');
1115     END IF;
1116 end if;
1117 
1118 if p_customer_trx_id is not null
1119 then
1120    IF PG_DEBUG in ('Y', 'C') THEN
1121       arp_standard.debug('customer trx id is not null....  ===  ' || to_char(p_customer_trx_id));
1122    END IF;
1123 
1124 insert into ra_cust_trx_line_gl_dist
1125  (POST_REQUEST_ID           ,
1126   POSTING_CONTROL_ID        ,
1127   ACCOUNT_CLASS             ,
1128   RA_POST_LOOP_NUMBER       ,
1129   CUSTOMER_TRX_ID           ,
1130   ACCOUNT_SET_FLAG          ,
1131   ACCTD_AMOUNT              ,
1132   USSGL_TRANSACTION_CODE    ,
1133   USSGL_TRANSACTION_CODE_CONTEXT  ,
1134   ATTRIBUTE11                     ,
1135   ATTRIBUTE12                     ,
1136   ATTRIBUTE13                     ,
1137   ATTRIBUTE14                     ,
1138   ATTRIBUTE15                     ,
1139   LATEST_REC_FLAG                 ,
1140   ORG_ID                          ,
1141   CUST_TRX_LINE_GL_DIST_ID        ,
1142   CUSTOMER_TRX_LINE_ID            ,
1143   CODE_COMBINATION_ID             ,
1144   SET_OF_BOOKS_ID                 ,
1145   LAST_UPDATE_DATE                ,
1146   LAST_UPDATED_BY                 ,
1147   CREATION_DATE                   ,
1148   CREATED_BY                      ,
1149   LAST_UPDATE_LOGIN               ,
1150   PERCENT                         ,
1151   AMOUNT                          ,
1152   GL_DATE                         ,
1153   GL_POSTED_DATE                  ,
1154   CUST_TRX_LINE_SALESREP_ID       ,
1155   COMMENTS                        ,
1156   ATTRIBUTE_CATEGORY              ,
1157   ATTRIBUTE1                      ,
1158   ATTRIBUTE2                      ,
1159   ATTRIBUTE3                      ,
1160   ATTRIBUTE4                      ,
1161   ATTRIBUTE5                      ,
1162   ATTRIBUTE6                      ,
1163   ATTRIBUTE7                      ,
1164   ATTRIBUTE8                      ,
1165   ATTRIBUTE9                      ,
1166   ATTRIBUTE10                     ,
1167   REQUEST_ID                      ,
1168   PROGRAM_APPLICATION_ID          ,
1169   PROGRAM_ID                      ,
1170   PROGRAM_UPDATE_DATE             ,
1171   CONCATENATED_SEGMENTS           ,
1172   ORIGINAL_GL_DATE                )
1173 select
1174 POST_REQUEST_ID,
1175 -3,
1176 'ROUND',
1177 RA_POST_LOOP_NUMBER,
1178 CUSTOMER_TRX_ID,
1179 ACCOUNT_SET_FLAG,
1180 NULL,  /* acctd_amount */
1181 USSGL_TRANSACTION_CODE,
1182 USSGL_TRANSACTION_CODE_CONTEXT,
1183 ATTRIBUTE11,
1184 ATTRIBUTE12,
1185 ATTRIBUTE13,
1186 ATTRIBUTE14,
1187 ATTRIBUTE15,
1188 NULL,      /* LATEST_REC_FLAG */
1189 ORG_ID,
1190 RA_CUST_TRX_LINE_GL_DIST_s.nextval,
1191 CUSTOMER_TRX_LINE_ID,
1192 P_TRX_HEADER_ROUND_CCID,  /* CODE_COMBINATION_ID */
1193 SET_OF_BOOKS_ID,
1194 SYSDATE,
1195 arp_global.last_updated_by,
1196 SYSDATE,
1197 arp_global.created_by,
1198 arp_global.last_update_login,
1199 PERCENT,
1200 NULL,    /* AMOUNT */
1201 GL_DATE,
1202 GL_POSTED_DATE,
1203 CUST_TRX_LINE_SALESREP_ID,
1204 COMMENTS,
1205 ATTRIBUTE_CATEGORY,
1206 ATTRIBUTE1,
1207 ATTRIBUTE2,
1208 ATTRIBUTE3,
1209 ATTRIBUTE4,
1210 ATTRIBUTE5,
1211 ATTRIBUTE6,
1212 ATTRIBUTE7,
1213 ATTRIBUTE8,
1214 ATTRIBUTE9,
1215 ATTRIBUTE10,
1216 arp_global.request_id,
1217 arp_global.program_application_id,
1218 arp_global.program_id,
1219 arp_global.program_update_date,
1220 CONCATENATED_SEGMENTS,
1221 ORIGINAL_GL_DATE
1222 from ra_cust_trx_line_gl_dist rec
1223 where account_class = 'REC'
1224 and   latest_rec_flag = 'Y'
1225 and   gl_posted_date is null
1226 and   rec.customer_trx_id = p_customer_trx_id
1227 /* bug3311759 : Removed
1228 and   not exists ( select 1
1229                    from   ra_cust_trx_line_gl_dist dist2
1230                    where  dist2.customer_trx_id = rec.customer_trx_id
1231                    and    dist2.account_class in ('UNEARN','UNBILL')
1232                    and    dist2.account_set_flag = 'N')
1233 */
1234 and   not exists ( select 1
1235                    from   ra_cust_trx_line_gl_dist dist2
1236                    where  dist2.customer_trx_id = rec.customer_trx_id
1237                    and    dist2.account_class = 'ROUND'
1238                    and    dist2.account_set_flag = rec.account_set_flag);
1239 
1240     rows := SQL%ROWCOUNT;
1241 
1242    IF ( rows > 0 ) THEN
1243         IF PG_DEBUG in ('Y', 'C') THEN
1244            arp_standard.debug('Rows were inserted into gl dist ');
1245         END IF;
1246 
1247          SELECT cust_trx_line_gl_dist_id
1248          BULK COLLECT INTO l_gl_dist_key_value_list
1249          FROM ra_cust_trx_line_gl_dist rec
1250          where  rec.customer_trx_id = p_customer_trx_id
1251          and  account_class = 'ROUND';
1252 
1253 
1254         /*-----------------------------------------------------+
1255          | call mrc engine to insert RA_CUST_TRX_LINES_GL_DIST |
1256          +-----------------------------------------------------*/
1257          IF PG_DEBUG in ('Y', 'C') THEN
1258             arp_standard.debug('before calling maintain_mrc ');
1259          END IF;
1260 
1261          ar_mrc_engine.maintain_mrc_data(
1262                     p_event_mode       => 'INSERT',
1263                     p_table_name       => 'RA_CUST_TRX_LINE_GL_DIST',
1264                     p_mode             => 'BATCH',
1265                     p_key_value_list   => l_gl_dist_key_value_list) ;
1266 
1267 --BUG#2750340
1268         /*-----------------------------------------------------+
1269          | Need to call ARP_XLA for denormalizing the event_id |
1270          | on round distribution                               |
1271          +-----------------------------------------------------*/
1272           l_xla_ev_rec.xla_from_doc_id := p_customer_trx_id;
1273           l_xla_ev_rec.xla_to_doc_id := p_customer_trx_id;
1274           l_xla_ev_rec.xla_doc_table := 'CT';
1275           l_xla_ev_rec.xla_mode := 'O';
1276           l_xla_ev_rec.xla_call := 'D';
1277           arp_xla_events.create_events(l_xla_ev_rec);
1278 
1279     END IF;
1280 IF PG_DEBUG in ('Y', 'C') THEN
1281    arp_standard.debug('after mrc if customer trx id is not null');
1282 END IF;
1283 
1284 end if;
1285 
1286   IF PG_DEBUG in ('Y', 'C') THEN
1287      arp_standard.debug(
1288           'Rows Processed: '||
1289            rows);
1290   END IF;
1291 
1292   p_rows_processed := p_rows_processed + rows;
1293 
1294   IF PG_DEBUG in ('Y', 'C') THEN
1295      arp_standard.debug('arp_rounding.insert_round_record()- ' ||
1296                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
1297   END IF;
1298 
1299   return(iTRUE);
1300 EXCEPTION
1301 	WHEN others THEN
1302         p_error_message := 'arp_rounding - ' || SQLERRM;
1303         return(iFALSE);
1304 end insert_round_records;
1305 
1306 /* Bug 2736599 - this routine has been obsoleted due to problems with
1307    header level rounding in conjunction with SUSPENSE accounts */
1308 
1309 FUNCTION get_line_round_acctd_amount( P_CUSTOMER_TRX_ID   IN NUMBER)
1310 
1311 RETURN NUMBER IS
1312 
1313 l_round_acctd_amount NUMBER;
1314 
1315 begin
1316 
1317  /*****************************************************
1318  * Bug 13434104                                       *
1319  * Removed the call to gl_currency_api.convert_amount *
1320  ******************************************************/
1321      select nvl(rec.acctd_amount,0) -
1322             sum( decode(fc.minimum_accountable_unit,
1323                         null, round(l.extended_amount *
1324                               nvl(ct.exchange_rate,1),
1325                                           fc.precision),
1326                         round( (l.extended_amount *
1327                                 nvl(ct.exchange_rate,1)
1328                                 ) / fc.minimum_accountable_unit
1329                                 ) * fc.minimum_accountable_unit
1330                         )
1331                   )
1332      into   l_round_acctd_amount
1333      from   ra_customer_trx ct,
1334             ra_customer_trx_lines l,
1335             ra_cust_trx_line_gl_dist rec,
1336             fnd_currencies fc,
1337             gl_sets_of_books gsb
1338      where  ct.customer_trx_id = l.customer_trx_id
1339      and    ct.customer_trx_id = rec.customer_trx_id
1340      and    ct.customer_trx_id = P_CUSTOMER_TRX_ID
1341      and    ct.set_of_books_id = gsb.set_of_books_id
1342      and    fc.currency_code   = gsb.currency_code
1343      and    rec.account_class = 'REC'
1344      and    rec.latest_rec_flag = 'Y'
1345      group by rec.acctd_amount;
1346 
1347      return l_round_acctd_amount;
1348 
1349 exception
1350 when no_data_found then
1351 return 0;
1352 
1353 end get_line_round_acctd_amount;
1354 
1355 /*************************************************************************
1356  PRIVATE FUNCTION     get_dist_round_acctd_amount                        *
1357  This function is obsolete as we are keeping the release 10 constraint   *
1358  Sum of all distribtions acctd_amount should be equal to the line amount *
1359  converted to functional currency.                                       *
1360 **************************************************************************/
1361 FUNCTION get_dist_round_acctd_amount(P_CUSTOMER_TRX_ID IN NUMBER)
1362 RETURN NUMBER IS
1363 
1364 l_round_acctd_amount NUMBER;
1365 
1366 begin
1367      select
1368               nvl(rec.acctd_amount,0) - sum(nvl(lgd.acctd_amount,0))
1369        into   l_round_acctd_amount
1370        from   ra_cust_trx_line_gl_dist lgd,
1371               ra_cust_trx_line_gl_dist rec
1372        where  lgd.customer_trx_id = rec.customer_trx_id
1373        and    rec.customer_trx_id = P_CUSTOMER_TRX_ID
1374        and    rec.account_class = 'REC'
1375        and    rec.latest_rec_flag = 'Y'
1376        and    lgd.account_set_flag = 'N'
1377        and    lgd.account_class not in ('REC', 'ROUND')
1378        group by rec.acctd_amount;
1379 
1380       return l_round_acctd_amount;
1381 
1382 exception
1383 when no_data_found then
1384 return 0;
1385 
1386 end get_dist_round_acctd_amount;
1387 
1388 /*-------------------------------------------------------------------------+
1389  | PRIVATE FUNCTION                                                        |
1390  |   correct_round_records()                                               |
1391  |                                                                         |
1392  | DESCRIPTION                                                             |
1393  |   This function calculates the rounding difference in the acctd_amount  |
1394  |   for a give transaction and update it's ROUND record with it.          |
1395  |                                                                         |
1396  |   The rounding difference is calculated as follows :                    |
1397  |                                                                         |
1398  |   round acctd_amount =                                                  |
1399  |         receivable acctd_amount -                                       |
1400  |         Sum( line amount converted to functional currency rounded for   |
1401  |              functional currency)                                       |
1402  |                                                                         |
1403  |   This function also update the following columns of the round record.  |
1404  |   amount = 0                                                            |
1405  |   code_combination_id = code_combination_id for ROUND account after     |
1406  |                         substituting the balancing segment with REC     |
1407  |                         account                                         |
1408  |   concatenated_segments = concatenated_segments returned by the         |
1409  |                           replace_balancing_segment function            |
1410  |                                                                         |
1411  | REQUIRES                                                                |
1412  |                                                                         |
1413  | RETURNS                                                                 |
1414  |   TRUE  if no errors occur                                              |
1415  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
1416  |                                                                         |
1417  | NOTES                                                                   |
1418  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
1419  |                                                                         |
1420  | EXAMPLE                                                                 |
1421  |                                                                         |
1422  | MODIFICATION HISTORY                                                    |
1423  |                                                                         |
1424  +-------------------------------------------------------------------------*/
1425 
1426 FUNCTION correct_round_records( P_REQUEST_ID IN NUMBER,
1427                                 P_CUSTOMER_TRX_ID       IN NUMBER,
1428                                 P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
1429                                 P_ROWS_PROCESSED    IN OUT NOCOPY NUMBER,
1430                                 P_ERROR_MESSAGE        OUT NOCOPY VARCHAR2,
1431                                 P_BASE_PRECISION        IN NUMBER,
1432                                 P_BASE_MAU              IN NUMBER,
1433                                 P_TRX_CLASS_TO_PROCESS  IN VARCHAR2,
1434                                 concat_segs             IN VARCHAR2,
1435                                 balanced_round_ccid     IN NUMBER)
1436  RETURN NUMBER IS
1437 
1438   /* Bug 2736599 - replaced get_line_round_acctd_amount with
1439        get_dist_round_acctd_amount to resolve issues with
1440        header level rounding and SUSPENSE accounts */
1441 
1442 l_line_round_acctd_amount number := nvl(get_dist_round_acctd_amount(P_CUSTOMER_TRX_ID),0);
1443 
1444 l_count number;
1445 
1446 begin
1447 
1448   IF PG_DEBUG in ('Y', 'C') THEN
1449      arp_standard.debug('arp_rounding.correct_round_record()+ ' ||
1450                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
1451    arp_standard.debug('P_CUSTOMER_TRX_ID: ' || P_CUSTOMER_TRX_ID);
1452 END IF;
1453 
1454 
1455 update ra_cust_trx_line_gl_dist dist
1456 set   (amount, acctd_amount, code_combination_id, concatenated_segments) =
1457       (select 0,
1458               l_line_round_acctd_amount,
1459               nvl(balanced_round_ccid,-1),
1460               concatenated_segments
1461        from   ra_customer_trx ct
1462        where  ct.customer_trx_id = dist.customer_trx_id
1463        ),
1464 last_updated_by = arp_global.last_updated_by,    /* Bug 2089972 */
1465 last_update_date = sysdate
1466 where  dist.customer_trx_id = P_CUSTOMER_TRX_ID
1467 and    dist.account_class = 'ROUND'
1468 and    dist.gl_posted_date is null
1469 and    (
1470         nvl(dist.amount,0) <>  0  OR
1471         nvl(dist.acctd_amount, 0)<> l_line_round_acctd_amount OR
1472         dist.code_combination_id <> nvl(balanced_round_ccid,-1) OR
1473         dist.acctd_amount is null OR
1474         dist.amount is null
1475         );
1476 
1477   l_count := SQL%ROWCOUNT;
1478 
1479   IF PG_DEBUG in ('Y', 'C') THEN
1480      arp_standard.debug('Rows Processed: '||
1481            l_count);
1482   END IF;
1483 
1484   p_rows_processed := p_rows_processed + l_count;
1485 
1486   /* MRC Processing */
1487   IF PG_DEBUG in ('Y', 'C') THEN
1488      arp_standard.debug('  doing rounding for MRC if necessary');
1489   END IF;
1490   ar_mrc_engine2.mrc_correct_rounding(
1491                    'CORRECT_ROUND_RECORDS',
1492                    P_REQUEST_ID,
1493                    P_CUSTOMER_TRX_ID,
1494                    P_CUSTOMER_TRX_LINE_ID,
1495                    P_TRX_CLASS_TO_PROCESS,
1496                    concat_segs,
1497                    balanced_round_ccid
1498                   );
1499 
1500   IF PG_DEBUG in ('Y', 'C') THEN
1501      arp_standard.debug( 'arp_rounding.correct_round_record()- ' ||
1502                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
1503   END IF;
1504 
1505   return(iTRUE);
1506 
1507 end correct_round_records;
1508 
1509 /*-------------------------------------------------------------------------+
1510  | PRIVATE FUNCTION                                                        |
1511  |   correct_receivables_header()                                          |
1512  |                                                                         |
1513  | DESCRIPTION                                                             |
1514  |   This function corrects rounding errors in the Receivable records.     |
1515  |   This is the only function that modifies account set records because   |
1516  |   only the Receivable account set record has an amount.                 |
1517  |   This function corrects errors 1 as specified in the high level        |
1518  |   design document (release 10).                                         |
1519  |   The REC acctd_amount is calculated as follows:                        |
1520  |   acctd_amount = REC amount converted to functional currency.           |
1521  |                                                                         |
1522  | REQUIRES                                                                |
1523  |                                                                         |
1524  | RETURNS                                                                 |
1525  |   TRUE  if no errors occur                                              |
1526  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
1527  |                                                                         |
1528  | NOTES                                                                   |
1529  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
1530  |                                                                         |
1531  | EXAMPLE                                                                 |
1532  |                                                                         |
1533  | MODIFICATION HISTORY                                                    |
1534  |                                                                         |
1535  +-------------------------------------------------------------------------*/
1536 FUNCTION correct_receivables_header(  P_REQUEST_ID IN NUMBER,
1537                                       P_CUSTOMER_TRX_ID       IN NUMBER,
1538                                       P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
1539                                       P_ROWS_PROCESSED    IN OUT NOCOPY NUMBER,
1540                                       P_ERROR_MESSAGE        OUT NOCOPY VARCHAR2,
1541                                       P_BASE_PRECISION        IN NUMBER,
1542                                       P_BASE_MAU              IN NUMBER,
1543                                       P_TRX_CLASS_TO_PROCESS  IN VARCHAR2)
1544                                    RETURN NUMBER IS
1545   l_count number;
1546 
1547 begin
1548 
1549   IF PG_DEBUG in ('Y', 'C') THEN
1550      arp_standard.debug('arp_rounding.correct_receivables_header()+ ' ||
1551                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
1552   END IF;
1553 
1554   if (p_request_id is not null)
1555   then
1556 
1557 /******************************************************
1558  * Bug 13434104                                       *
1559  * Removed the call to gl_currency_api.convert_amount *
1560  ******************************************************/
1561 
1562 update ra_cust_trx_line_gl_dist rec
1563 set (amount, acctd_amount, percent) =
1564     ( select nvl(rec.amount, 0) +
1565              (sum(l.extended_amount) - nvl(rec.amount, 0) ),
1566              nvl(rec.acctd_amount, 0) +
1567              ( decode(p_base_mau,
1568                       null, round(sum(l.extended_amount) *
1569                               max(nvl(exchange_rate,1)),
1570                               p_base_precision),
1571                       round( (sum(l.extended_amount) *
1572                                 max(nvl(exchange_rate,1))
1573                                ) / p_base_mau
1574                               ) * p_base_mau
1575                       )
1576               - nvl(rec.acctd_amount, 0)
1577              ),    /* acctd_amount */
1578             rec.percent + (100 - rec.percent) /* percent */
1579       from  ra_customer_trx t,
1580             ra_customer_trx_lines l
1581       where t.customer_trx_id = l.customer_trx_id
1582       and   t.customer_trx_id = rec.customer_trx_id
1583       group by l.customer_trx_id,
1584                t.trx_number,
1585                t.exchange_rate_type,
1586                t.invoice_currency_code,
1587                t.exchange_date,
1588                exchange_rate
1589  ),
1590 last_updated_by = arp_global.last_updated_by,   /* Bug 2089972 */
1591 last_update_date = sysdate
1592 where customer_trx_id in
1593     ( select l.customer_trx_id
1594       from   ra_customer_trx_lines l,
1595              ra_customer_trx t,
1596              ra_cust_trx_line_gl_dist d
1597       where  t.customer_trx_id = l.customer_trx_id
1598       and    t.customer_trx_id = d.customer_trx_id
1599       and    d.account_class   = 'REC'
1600       and    d.latest_rec_flag = 'Y'
1601    /*-------------------------------------------
1602                  ---CUT HERE---                */
1603       and    d.request_id      = p_request_id
1604    /*                                          *
1605     *------------------------------------------*/
1606       and    nvl(t.previous_customer_trx_id, -1) =
1607                 decode(p_trx_class_to_process,
1608                        'INV',        -1,
1609                        'REGULAR_CM', t.previous_customer_trx_id,
1610                                      nvl(t.previous_customer_trx_id, -1) )
1611       having (
1612                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
1613                100 <> nvl(d.percent, 0) OR
1614                       decode(p_base_mau,
1615                              null, round(sum(l.extended_amount) *
1616                                   max(nvl(exchange_rate,1)),
1617                                   p_base_precision),
1618                               round( (sum(l.extended_amount) *
1619                                     max(nvl(exchange_rate,1))
1620                                    ) / p_base_mau
1621                                  ) * p_base_mau
1622                              )
1623                   <> nvl(d.acctd_amount, 0) OR
1624                d.acctd_amount is null OR
1625                d.amount is null
1626              )
1627       group by l.customer_trx_id,
1628                t.trx_number,
1629                d.amount,
1630                d.acctd_amount,
1631                d.percent,
1632                t.invoice_currency_code,
1633                t.exchange_date,
1634                t.exchange_rate_type,
1635                exchange_rate
1636  )
1637 and rec.account_class = 'REC'
1638 and rec.gl_posted_date is null;
1639 
1640   end if; /* request_id case */
1641 
1642   if (p_customer_trx_id is not null)
1643   then
1644 
1645 /******************************************************
1646  * Bug 13434104                                       *
1647  * Removed the call to gl_currency_api.convert_amount *
1648  ******************************************************/
1649 
1650   /* 7039838 - If executed from autoinv, then added several hints
1651       and additional binds for performance */
1652      IF g_autoinv
1653      THEN
1654 update ra_cust_trx_line_gl_dist rec
1655 set (amount, acctd_amount, percent) =
1656     ( select /*+ index(L RA_CUSTOMER_TRX_LINES_N4) */
1657              nvl(rec.amount, 0) +
1658              (sum(l.extended_amount) - nvl(rec.amount, 0) ),
1659              nvl(rec.acctd_amount, 0) +
1660              ( decode(p_base_mau,
1661                      null, round(sum(l.extended_amount) *
1662                                  max(nvl(exchange_rate,1)),
1663                                  p_base_precision),
1664                            round( (sum(l.extended_amount) *
1665                                    max(nvl(exchange_rate,1))
1666                                   ) / p_base_mau
1667                                  ) * p_base_mau
1668                      )
1669               - nvl(rec.acctd_amount, 0)
1670              ),    /* acctd_amount */
1671             rec.percent + (100 - rec.percent) /* percent */
1672       from  ra_customer_trx t,
1673             ra_customer_trx_lines l
1674       where t.customer_trx_id = l.customer_trx_id
1675       and   l.customer_trx_id = rec.customer_trx_id
1676       and   l.request_id = g_autoinv_request_id -- 7039838
1677       group by l.customer_trx_id,
1678                t.trx_number,
1679                t.invoice_currency_code,
1680                t.exchange_date,
1681                t.exchange_rate_type,
1682                exchange_rate
1683  ),
1684 last_updated_by = arp_global.last_updated_by,   /*Bug 2089972 */
1685 last_update_date = sysdate
1686 where customer_trx_id in
1687     ( select /*+ leading(T,D,L) use_hash(L)
1688                  index(L RA_CUSTOMER_TRX_LINES_N4) */
1689              l.customer_trx_id
1690       from   ra_customer_trx t,
1691              ra_customer_trx_lines l,
1692              ra_cust_trx_line_gl_dist d
1693       where  t.customer_trx_id = l.customer_trx_id
1694       and    l.customer_trx_id = d.customer_trx_id
1695       and    l.request_id = g_autoinv_request_id   -- 7039838
1696       and    l.customer_trx_id = p_customer_trx_id -- 7039838
1697       and    d.account_class   = 'REC'
1698       and    d.latest_rec_flag = 'Y'
1699    /*-------------------------------------------------
1700                     ---CUT HERE---                   */
1701       and    d.customer_trx_id = p_customer_trx_id
1702    /*
1703     *------------------------------------------------*/
1704       and    nvl(t.previous_customer_trx_id, -1) =
1705                 decode(p_trx_class_to_process,
1706                        'INV',        -1,
1707                        'REGULAR_CM', t.previous_customer_trx_id,
1708                                      nvl(t.previous_customer_trx_id, -1) )
1709       having (
1710                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
1711                100 <> nvl(d.percent, 0) OR
1712                decode(p_base_mau,
1713                       null, round(sum(l.extended_amount) *
1714                                   max(nvl(exchange_rate,1)),
1715                                   p_base_precision),
1716                             round( (sum(l.extended_amount) *
1717                                     max(nvl(exchange_rate,1))
1718                                    ) / p_base_mau
1719                                  ) * p_base_mau
1720                        )
1721                   <> nvl(d.acctd_amount, 0) OR
1722                d.acctd_amount is null OR
1723                d.amount is null
1724              )
1725       group by l.customer_trx_id,
1726                t.trx_number,
1727                d.amount,
1728                d.acctd_amount,
1729                d.percent,
1730                t.invoice_currency_code,
1731                t.exchange_date,
1732                t.exchange_rate_type,
1733                exchange_rate
1734  )
1735 and rec.account_class = 'REC'
1736 and rec.gl_posted_date is null;
1737 
1738      ELSE
1739 
1740      /* Not autoinvoice, probably Rev Rec or forms logic */
1741 update ra_cust_trx_line_gl_dist rec
1742 set (amount, acctd_amount, percent) =
1743     ( select nvl(rec.amount, 0) +
1744              (sum(l.extended_amount) - nvl(rec.amount, 0) ),
1745              nvl(rec.acctd_amount, 0) +
1746              ( decode(p_base_mau,
1747                      null, round(sum(l.extended_amount) *
1748                                  max(nvl(exchange_rate,1)),
1749                                  p_base_precision),
1750                            round( (sum(l.extended_amount) *
1751                                    max(nvl(exchange_rate,1))
1752                                   ) / p_base_mau
1753                                  ) * p_base_mau
1754                      )
1755               - nvl(rec.acctd_amount, 0)
1756              ),    /* acctd_amount */
1757             rec.percent + (100 - rec.percent) /* percent */
1758       from  ra_customer_trx t,
1759             ra_customer_trx_lines l
1760       where t.customer_trx_id = l.customer_trx_id
1761       and   l.customer_trx_id = rec.customer_trx_id
1762       group by l.customer_trx_id,
1763                t.trx_number,
1764                t.invoice_currency_code,
1765                t.exchange_date,
1766                t.exchange_rate_type,
1767                exchange_rate
1768  ),
1769 last_updated_by = arp_global.last_updated_by,   /*Bug 2089972 */
1770 last_update_date = sysdate
1771 where customer_trx_id in
1772     ( select l.customer_trx_id
1773       from   ra_customer_trx t,
1774              ra_customer_trx_lines l,
1775              ra_cust_trx_line_gl_dist d
1776       where  t.customer_trx_id = l.customer_trx_id
1777       and    l.customer_trx_id = d.customer_trx_id
1778       and    d.account_class   = 'REC'
1779       and    d.latest_rec_flag = 'Y'
1780    /*-------------------------------------------------
1781                     ---CUT HERE---                   */
1782       and    d.customer_trx_id = p_customer_trx_id
1783    /*
1784     *------------------------------------------------*/
1785       and    nvl(t.previous_customer_trx_id, -1) =
1786                 decode(p_trx_class_to_process,
1787                        'INV',        -1,
1788                        'REGULAR_CM', t.previous_customer_trx_id,
1789                                      nvl(t.previous_customer_trx_id, -1) )
1790       having (
1791                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
1792                100 <> nvl(d.percent, 0) OR
1793                decode(p_base_mau,
1794                       null, round(sum(l.extended_amount) *
1795                                   max(nvl(exchange_rate,1)),
1796                                   p_base_precision),
1797                             round( (sum(l.extended_amount) *
1798                                     max(nvl(exchange_rate,1))
1799                                    ) / p_base_mau
1800                                  ) * p_base_mau
1801                        )
1802                   <> nvl(d.acctd_amount, 0) OR
1803                d.acctd_amount is null OR
1804                d.amount is null
1805              )
1806       group by l.customer_trx_id,
1807                t.trx_number,
1808                d.amount,
1809                d.acctd_amount,
1810                d.percent,
1811                t.invoice_currency_code,
1812                t.exchange_date,
1813                t.exchange_rate_type,
1814                exchange_rate
1815  )
1816 and rec.account_class = 'REC'
1817 and rec.gl_posted_date is null;
1818 
1819      END IF; /* g_autoinv case */
1820   end if; /* customer_trx_id case */
1821 
1822   l_count := SQL%ROWCOUNT;
1823 
1824   IF PG_DEBUG in ('Y', 'C') THEN
1825      arp_standard.debug('Rows Processed: '||
1826            l_count);
1827   END IF;
1828 
1829   p_rows_processed := p_rows_processed + l_count;
1830 
1831   IF PG_DEBUG in ('Y', 'C') THEN
1832      arp_standard.debug( 'arp_rounding.correct_receivables_header()- ' ||
1833                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
1834   END IF;
1835 
1836   /* MRC Processing */
1837   IF PG_DEBUG in ('Y', 'C') THEN
1838      arp_standard.debug('  doing rounding for MRC if necessary');
1839   END IF;
1840   ar_mrc_engine2.mrc_correct_rounding(
1841                    'CORRECT_RECEIVABLES_HEADER',
1842                    P_REQUEST_ID,
1843                    P_CUSTOMER_TRX_ID,
1844                    P_CUSTOMER_TRX_LINE_ID,
1845                    P_TRX_CLASS_TO_PROCESS
1846                   );
1847 
1848   return(iTRUE);
1849 
1850 end correct_receivables_header;
1851 
1852 /*-------------------------------------------------------------------------+
1853  | PRIVATE FUNCTION                                                        |
1854  |   correct_receivables_records()                                         |
1855  |                                                                         |
1856  | DESCRIPTION                                                             |
1857  |   This function corrects rounding errors in the Receivable records.     |
1858  |   This is the only function that modifies account set records because   |
1859  |   only the Receivable account set record has an amount.                 |
1860  |   This function corrects errors 1 and 2 as specified in the high level  |
1861  |   design document.                                                      |
1862  |                                                                         |
1863  | REQUIRES                                                                |
1864  |   All IN parameters                                                     |
1865  |                                                                         |
1866  | RETURNS                                                                 |
1867  |   TRUE  if no errors occur                                              |
1868  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
1869  |                                                                         |
1870  | NOTES                                                                   |
1871  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
1872  |                                                                         |
1873  | EXAMPLE                                                                 |
1874  |                                                                         |
1875  | MODIFICATION HISTORY                                                    |
1876  |                                                                         |
1877  | Nilesh Acharya   24-July-98    Changes for triangulation                |
1878  |                                                                         |
1879  +-------------------------------------------------------------------------*/
1880 
1881 FUNCTION correct_receivables_records(
1882 		P_REQUEST_ID            IN NUMBER,
1883                 P_CUSTOMER_TRX_ID       IN NUMBER,
1884                 P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
1885                 P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
1886                 P_ERROR_MESSAGE         OUT NOCOPY VARCHAR2,
1887                 P_BASE_PRECISION        IN NUMBER,
1888                 P_BASE_MAU              IN NUMBER,
1889                 P_TRX_CLASS_TO_PROCESS  IN VARCHAR2)
1890 
1891          RETURN NUMBER IS
1892   l_count number;
1893 BEGIN
1894 
1895   IF PG_DEBUG in ('Y', 'C') THEN
1896      arp_standard.debug('arp_rounding.correct_receivables_record()+ ' ||
1897                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
1898   END IF;
1899 
1900   IF (p_request_id IS NOT NULL)
1901   THEN
1902 
1903 /******************************************************
1904  * Bug 13434104                                       *
1905  * Removed the call to gl_currency_api.convert_amount *
1906  ******************************************************/
1907 
1908 UPDATE ra_cust_trx_line_gl_dist rec
1909 SET (amount, acctd_amount, percent) =
1910     ( SELECT
1911              NVL(rec.amount, 0) +
1912              (SUM(l.extended_amount) - NVL(rec.amount, 0) ),
1913              NVL(rec.acctd_amount, 0) +
1914              (
1915               sum( decode(p_base_mau,
1916                           null, round(l.extended_amount *
1917                                  nvl(exchange_rate,1),
1918                                  p_base_precision),
1919                            round( (l.extended_amount *
1920                                    nvl(exchange_rate,1)
1921                                    ) / p_base_mau
1922                                  ) * p_base_mau
1923                            )
1924                   )
1925                  - NVL(rec.acctd_amount, 0)
1926              ),    /* acctd_amount */
1927             rec.percent + (100 - rec.percent) /* percent */
1928       FROM
1929             ra_customer_trx_lines l,
1930             ra_customer_trx t
1931       WHERE
1932             t.customer_trx_id = rec.customer_trx_id
1933       AND   l.customer_trx_id = t.customer_trx_id
1934       GROUP BY
1935             l.customer_trx_id,
1936             t.trx_number
1937     ),
1938 last_updated_by = arp_global.last_updated_by,       /* Bug 2089972 */
1939 last_update_date = sysdate
1940 WHERE customer_trx_id IN
1941     ( SELECT
1942              l.customer_trx_id
1943       FROM
1944              ra_customer_trx_lines l,
1945              ra_customer_trx t,
1946              ra_cust_trx_line_gl_dist d
1947       WHERE
1948              t.customer_trx_id = d.customer_trx_id
1949       AND    l.customer_trx_id = t.customer_trx_id
1950       AND    d.account_class   = 'REC'
1951       AND    d.latest_rec_flag = 'Y'
1952    /*-------------------------------------------
1953                  ---CUT HERE---                */
1954       AND    d.request_id      = p_request_id
1955    /*                                          *
1956     *------------------------------------------*/
1957       AND    NVL(t.previous_customer_trx_id, -1) =
1958                 DECODE(p_trx_class_to_process,
1959                        'INV',        -1,
1960                        'REGULAR_CM', t.previous_customer_trx_id,
1961                                      nvl(t.previous_customer_trx_id, -1) )
1962       having (
1963                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
1964                100 <> nvl(d.percent, 0) OR
1965               sum(
1966                                 decode(p_base_mau,
1967                                        null, round(l.extended_amount *
1968                                              nvl(exchange_rate,1),
1969                                              p_base_precision),
1970                                        round( (l.extended_amount *
1971                                                nvl(exchange_rate,1)
1972                                                ) / p_base_mau
1973                                              ) * p_base_mau
1974                                        )
1975                    )
1976                   <> nvl(d.acctd_amount, 0) OR
1977                d.acctd_amount is null OR
1978                d.amount is null
1979              )
1980       GROUP BY
1981                l.customer_trx_id,
1982                t.trx_number,
1983                d.amount,
1984                d.acctd_amount,
1985                d.percent
1986     )
1987 AND rec.account_class  = 'REC'
1988 AND rec.gl_posted_date IS NULL;
1989 
1990   END IF; /* request_id case */
1991 
1992   IF (p_customer_trx_id IS NOT NULL)
1993   THEN
1994 
1995 UPDATE ra_cust_trx_line_gl_dist rec
1996 SET (amount, acctd_amount, percent) =
1997     ( SELECT
1998              NVL(rec.amount, 0) +
1999              (SUM(l.extended_amount) - NVL(rec.amount, 0) ),
2000              NVL(rec.acctd_amount, 0) +
2001              (
2002               sum(
2003                                 decode(p_base_mau,
2004                                        null, round(l.extended_amount *
2005                                              nvl(exchange_rate,1),
2006                                              p_base_precision),
2007                                        round( (l.extended_amount *
2008                                                nvl(exchange_rate,1)
2009                                                ) / p_base_mau
2010                                              ) * p_base_mau
2011                                        )
2012                    )
2013                  - NVL(rec.acctd_amount, 0)
2014              ),
2015             rec.percent + (100 - rec.percent) /* percent */
2016       FROM
2017             ra_customer_trx_lines l,
2018             ra_customer_trx t
2019       WHERE
2020             t.customer_trx_id = rec.customer_trx_id
2021       AND   l.customer_trx_id = t.customer_trx_id
2022       GROUP BY
2023             l.customer_trx_id,
2024             t.trx_number
2025     ),
2026 last_updated_by = arp_global.last_updated_by,                /* Bug 2089972 */
2027 last_update_date = sysdate
2028 WHERE customer_trx_id IN
2029     ( SELECT
2030              l.customer_trx_id
2031       FROM
2032              ra_customer_trx t,
2033              ra_customer_trx_lines l,
2034              ra_cust_trx_line_gl_dist d
2035       WHERE
2036              t.customer_trx_id = d.customer_trx_id
2037       AND    l.customer_trx_id = t.customer_trx_id
2038       AND    d.account_class   = 'REC'
2039       AND    d.latest_rec_flag = 'Y'
2040    /*-------------------------------------------------
2041                     ---CUT HERE---                   */
2042       AND    d.customer_trx_id = p_customer_trx_id
2043    /*
2044     *------------------------------------------------*/
2045       AND    NVL(t.previous_customer_trx_id, -1) =
2046                 DECODE(p_trx_class_to_process,
2047                        'INV', -1,
2048                        'REGULAR_CM', t.previous_customer_trx_id,
2049                                      nvl(t.previous_customer_trx_id, -1) )
2050       having (
2051                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
2052                100 <> nvl(d.percent, 0) OR
2053               sum(
2054                                 decode(p_base_mau,
2055                                        null, round(l.extended_amount *
2056                                              nvl(exchange_rate,1),
2057                                              p_base_precision),
2058                                        round( (l.extended_amount *
2059                                                nvl(exchange_rate,1)
2060                                                ) / p_base_mau
2061                                              ) * p_base_mau
2062                                        )
2063                    )
2064                   <> nvl(d.acctd_amount, 0) OR
2065                d.acctd_amount is null OR
2066                d.amount is null
2067              )
2068       GROUP BY
2069                l.customer_trx_id,
2070                t.trx_number,
2071                d.amount,
2072                d.acctd_amount,
2073                d.percent
2074     )
2075 AND rec.account_class  = 'REC'
2076 AND rec.gl_posted_date IS NULL;
2077 
2078   END IF; /* customer_trx_id case */
2079 
2080 
2081   l_count := sql%rowcount;
2082 
2083   IF PG_DEBUG in ('Y', 'C') THEN
2084      arp_standard.debug(
2085           'Rows Processed: '||
2086            l_count);
2087   END IF;
2088 
2089   p_rows_processed := p_rows_processed + l_count;
2090 
2091   IF PG_DEBUG in ('Y', 'C') THEN
2092      arp_standard.debug('arp_rounding.correct_receivables_record()- ' ||
2093                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
2094   END IF;
2095 
2096   /* MRC Processing */
2097   IF PG_DEBUG in ('Y', 'C') THEN
2098      arp_standard.debug('doing rounding for MRC if necessary');
2099   END IF;
2100   ar_mrc_engine2.mrc_correct_rounding(
2101                    'CORRECT_RECEIVABLES_RECORDS',
2102                    P_REQUEST_ID,
2103                    P_CUSTOMER_TRX_ID,
2104                    P_CUSTOMER_TRX_LINE_ID,
2105                    P_TRX_CLASS_TO_PROCESS
2106                   );
2107 
2108   RETURN( iTRUE );
2109 EXCEPTION
2110   WHEN others THEN
2111     p_error_message := SQLERRM;
2112     IF PG_DEBUG in ('Y', 'C') THEN
2113        arp_standard.debug('EXCEPTION:  arp_rounding.correct_receivables_record()- '||
2114                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
2115     END IF;
2116     RETURN(iFALSE);
2117 
2118 END correct_receivables_records;
2119 
2120 /*-------------------------------------------------------------------------+
2121  | PRIVATE FUNCTION                                                        |
2122  |   correct_nonrule_line_records()                                        |
2123  |                                                                         |
2124  | DESCRIPTION                                                             |
2125  |   This function corrects errors in the tax, freight, charges and        |
2126  |   AutoInvoice Clearing lines as well as in LINE lines that do not       |
2127  |   use rules.                                                            |
2128  |   This function corrects errors 3 - 8 as specified in the high level    |
2129  |   design document.                                                      |
2130  |                                                                         |
2131  | REQUIRES                                                                |
2132  |   All IN parameters                                                     |
2133  |                                                                         |
2134  | RETURNS                                                                 |
2135  |   TRUE  if no errors occur                                              |
2136  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
2137  |                                                                         |
2138  | NOTES                                                                   |
2139  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
2140  |                                                                         |
2141  | EXAMPLE                                                                 |
2142  |                                                                         |
2143  | MODIFICATION HISTORY                                                    |
2144  |                                                                         |
2145  |    15-NOV-98      Manoj Gudivaka   Fix for Bug 718096)                  |
2146  |    29-JUL-02      M Raymond        Added hints for bug 2398437
2147  |    07-OCT-02      M Raymond        Restructured nonrule sql to
2148  |                                    resolve performance problem from
2149  |                                    bug 2539296.
2150  |    14-MAY-08      M Raymond       7039838 Performance tuning
2151  +-------------------------------------------------------------------------*/
2152  /*------------------------------------------------------------------------+
2153  | Modification for bug 718096                                             |
2154  |                                                                         |
2155  | Removed "account class" from the group by clause so that the rounding is|
2156  | done on the whole transaction amount rather than indiviually for the    |
2157  | Revenue amount and the Suspense Amount.                                 |
2158  |                                                                         |
2159  | The following Decode statement has been removed and replaced with       |
2160  | just the "extended amount"                                              |
2161  |                                                                         |
2162  |     DECODE(lgd2.account_class,                                          |
2163  |                         'REV', ctl.revenue_amount,                      |
2164  |                    'SUSPENSE', ctl.extended_amount - ctl.revenue_amount,|
2165  |                                ctl.extended_amount)                     |
2166  |                                                                         |
2167  +-------------------------------------------------------------------------*/
2168 
2169 FUNCTION correct_nonrule_line_records(
2170 		P_REQUEST_ID            IN NUMBER,
2171                 P_CUSTOMER_TRX_ID       IN NUMBER,
2172                 P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
2173                 P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
2174                 P_ERROR_MESSAGE         OUT NOCOPY VARCHAR2,
2175                 P_BASE_PRECISION        IN NUMBER,
2176                 P_BASE_MAU              IN NUMBER,
2177                 P_TRX_CLASS_TO_PROCESS  IN VARCHAR2)
2178 
2179          RETURN NUMBER IS
2180   l_count number;
2181 
2182 BEGIN
2183 
2184   IF PG_DEBUG in ('Y', 'C') THEN
2185      arp_standard.debug('arp_rounding.correct_nonrule_line_records()+ ' ||
2186                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
2187   END IF;
2188 
2189   IF (p_request_id IS NOT NULL)
2190   THEN
2191 
2192   /* Bug 2539296 - The sql below was slightly restructured for better
2193      performance in large databases.  I basically restructured the join
2194      order around ra_customer_trx instead of the gl_dist tables.
2195   */
2196 
2197 UPDATE ra_cust_trx_line_gl_dist lgd
2198 SET    (amount, acctd_amount)  =
2199        (SELECT /*+ index(rec1 RA_CUST_TRX_LINE_GL_DIST_N6) ordered */ NVL(lgd.amount, 0) -
2200                             (
2201                              SUM(lgd2.amount) -
2202                               (
2203                                  DECODE(lgd.gl_date,
2204                                         rec1.gl_date, 1,
2205                                         0) *
2206                                         ctl.extended_amount
2207                               )
2208                             ),  /* entered amount */
2209                NVL(lgd.acctd_amount, 0) -
2210                  (
2211                    SUM(lgd2.acctd_amount) -
2212                    (
2213                      DECODE(lgd.gl_date,
2214                             rec1.gl_date, 1,
2215                             0) *
2216                      DECODE(p_base_mau,
2217                                   NULL, ROUND( ctl.extended_amount *
2218                                                NVL(ct.exchange_rate,1),
2219                                                p_base_precision),
2220                                         ROUND( ( ctl.extended_amount *
2221                                                  NVL(ct.exchange_rate,1)
2222                                                ) / p_base_mau ) * p_base_mau
2223                            )
2224                    )
2225                  )              /* accounted amount */
2226                  FROM
2227                           ra_customer_trx_lines ctl,
2228                           ra_customer_trx ct,
2229                           ra_cust_trx_line_gl_dist lgd2,
2230                           ra_cust_trx_line_gl_dist rec1
2231                  WHERE
2232                           ctl.customer_trx_line_id = lgd2.customer_trx_line_id
2233                  AND      ctl.customer_trx_id      = ct.customer_trx_id
2234                  AND      lgd.customer_trx_line_id = ctl.customer_trx_line_id
2235 -- 718096          AND      lgd.account_class        = lgd2.account_class
2236                  AND      lgd2.account_set_flag    = 'N'
2237                  AND      rec1.customer_trx_id     = ct.customer_trx_id
2238                  AND      rec1.account_class       = 'REC'
2239                  AND      rec1.latest_rec_flag     = 'Y'
2240                  AND      NVL(lgd.gl_date, to_date( 2415021, 'J') )  =
2241                           NVL(lgd2.gl_date, to_date( 2415021, 'J') )
2242                  GROUP BY
2243                           ctl.customer_trx_line_id,
2244 -- 718096                   lgd2.account_class,
2245                           rec1.gl_date,
2246                           ctl.extended_amount,
2247                           ctl.revenue_amount,
2248                           ct.exchange_rate
2249        ),
2250        percent =
2251        (SELECT /*+ index(rec2 RA_CUST_TRX_LINE_GL_DIST_N6) */  DECODE(lgd.account_class || lgd.account_set_flag,
2252                          'SUSPENSEN', lgd.percent,
2253                          'UNBILLN', lgd.percent,
2254                          'UNEARNN', lgd.percent,
2255                          NVL(lgd.percent, 0) -
2256                                (
2257                                  SUM(NVL(lgd4.percent, 0))
2258                                      - DECODE(rec2.gl_date,
2259                                               NVL(lgd.gl_date,
2260                                                   rec2.gl_date), 100,
2261                                               0)
2262                                )
2263                         )  /* percent */
2264         FROM
2265                   ra_cust_trx_line_gl_dist lgd4,
2266                   ra_cust_trx_line_gl_dist rec2
2267         WHERE
2268                   lgd.customer_trx_line_id = lgd4.customer_trx_line_id
2269         AND       rec2.customer_trx_id     = lgd.customer_trx_id
2270 	AND       rec2.customer_trx_id     = lgd4.customer_trx_id
2271         AND       rec2.account_class       = 'REC'
2272         AND       rec2.latest_rec_flag     = 'Y'
2273         AND       lgd4.account_set_flag    = lgd.account_set_flag
2274         AND       DECODE(lgd4.account_set_flag,
2275                          'Y', lgd4.account_class,
2276                          lgd.account_class) = lgd.account_class
2277         AND       NVL(lgd.gl_date, to_date( 2415021, 'J') )  =
2278                   NVL(lgd4.gl_date, to_date( 2415021, 'J') )
2279         GROUP BY
2280                   rec2.gl_date,
2281                   lgd.gl_date
2282        ),
2283 last_updated_by = arp_global.last_updated_by,   /* Bug 2089972 */
2284 last_update_date = sysdate
2285  WHERE cust_trx_line_gl_dist_id  IN
2286        (SELECT /*+ index(rec3 RA_CUST_TRX_LINE_GL_DIST_N6) */
2287                MIN(DECODE(lgd3.gl_posted_date,
2288                           NULL, lgd3.cust_trx_line_gl_dist_id,
2289                           NULL) )
2290         FROM
2291                ra_customer_trx_lines ctl,
2292                ra_customer_trx t,
2293                ra_cust_trx_line_gl_dist lgd3,
2294                ra_cust_trx_line_gl_dist rec3
2295         WHERE
2296                t.request_id         = p_request_id
2297         AND    T.CUSTOMER_TRX_ID    = CTL.CUSTOMER_TRX_ID
2298         AND   (CTL.LINE_TYPE IN ( 'TAX','FREIGHT','CHARGES','SUSPENSE'  ) OR
2299               (CTL.LINE_TYPE = 'LINE'  AND CTL.ACCOUNTING_RULE_ID IS NULL ))
2300         AND    LGD3.CUSTOMER_TRX_LINE_ID = CTL.CUSTOMER_TRX_LINE_ID
2301         AND    LGD3.ACCOUNT_SET_FLAG = 'N'
2302         AND    REC3.CUSTOMER_TRX_ID = T.CUSTOMER_TRX_ID
2303         AND    REC3.ACCOUNT_CLASS = 'REC'
2304         AND    REC3.LATEST_REC_FLAG = 'Y'
2305         AND    NVL(t.previous_customer_trx_id, -1) =
2306                 DECODE(p_trx_class_to_process,
2307                        'INV', -1,
2308                        'REGULAR_CM', t.previous_customer_trx_id,
2309                        NVL(t.previous_customer_trx_id, -1) )
2310         GROUP BY
2311                  ctl.customer_trx_line_id,
2312 --  718096         lgd3.account_class,
2313                  lgd3.gl_date,
2314                  rec3.gl_date,
2315                  ctl.extended_amount,
2316                  ctl.revenue_amount,
2317                  t.exchange_rate
2318         HAVING (
2319                   SUM(NVL(lgd3.amount, 0))
2320                                   <> ctl.extended_amount *
2321                                      DECODE(lgd3.gl_date,
2322                                             rec3.gl_date, 1,
2323                                             0)
2324                 OR
2325                   SUM(NVL(lgd3.acctd_amount, 0)) <>
2326                   DECODE(lgd3.gl_date,
2327                          rec3.gl_date, 1,
2328                          0) *
2329                   DECODE(p_base_mau,
2330                          NULL, ROUND( ctl.extended_amount *
2331                                       NVL(t.exchange_rate,1),
2332                                       p_base_precision ),
2333                                ROUND( ( ctl.extended_amount *
2334                                        NVL(t.exchange_rate,1)
2335                                       ) / p_base_mau ) * p_base_mau
2336                         )
2337                )
2338        UNION
2339        SELECT /*+ index(rec5 RA_CUST_TRX_LINE_GL_DIST_N6) INDEX (lgd5 ra_cust_trx_line_gl_dist_n6) index(ctl2 ra_customer_trx_lines_u1) */
2340              TO_NUMBER(
2341                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
2342                                     lgd5.account_set_flag,
2343                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
2344                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
2345                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
2346                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
2347                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
2348                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
2349                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
2350                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
2351                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
2352                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
2353                                      NULL ) )
2354                       )
2355        FROM
2356               ra_cust_trx_line_gl_dist lgd5,
2357               ra_cust_trx_line_gl_dist rec5,
2358               ra_customer_trx_lines ctl2,
2359               ra_customer_trx t
2360        WHERE
2361               T.REQUEST_ID = p_request_id
2362        AND    T.CUSTOMER_TRX_ID = REC5.CUSTOMER_TRX_ID
2363        AND    CTL2.CUSTOMER_TRX_LINE_ID = LGD5.CUSTOMER_TRX_LINE_ID
2364        AND    REC5.CUSTOMER_TRX_ID = LGD5.CUSTOMER_TRX_ID
2365        AND    REC5.ACCOUNT_CLASS = 'REC'
2366        AND    REC5.LATEST_REC_FLAG = 'Y'
2367        AND   (CTL2.LINE_TYPE IN ( 'TAX','FREIGHT','CHARGES','SUSPENSE')
2368                 OR
2369              (CTL2.LINE_TYPE = 'LINE'  AND
2370              (CTL2.ACCOUNTING_RULE_ID IS NULL  OR LGD5.ACCOUNT_SET_FLAG = 'Y' )))
2371        GROUP BY
2372                 lgd5.customer_trx_line_id,
2373                 lgd5.gl_date,
2374                 rec5.gl_date,
2375                 lgd5.account_set_flag,
2376                 DECODE(lgd5.account_set_flag,
2377                        'N', NULL,
2378                        lgd5.account_class)
2379        HAVING
2380               SUM(NVL(lgd5.percent, 0)) <>
2381                  DECODE( NVL(lgd5.gl_date, rec5.gl_date),
2382                          rec5.gl_date, 100,
2383                          0)
2384      );
2385 
2386    END IF;  /* request_id case */
2387 
2388    IF (p_customer_trx_id IS NOT NULL AND p_customer_trx_line_id IS NULL)
2389    THEN
2390 
2391       IF g_autoinv
2392       THEN
2393          /* version tuned for autoinvoice with request_id joins */
2394 UPDATE ra_cust_trx_line_gl_dist lgd
2395 SET    (amount, acctd_amount)  =
2396        (SELECT /*+ index(LGD2 RA_CUST_TRX_LINE_GL_DIST_N10) */
2397                    NVL(lgd.amount, 0) -
2398                             (
2399                              SUM(lgd2.amount) -
2400                              (
2401                                  DECODE(lgd.gl_date,
2402                                         rec1.gl_date, 1,
2403                                         0) *
2404                                  DECODE(DECODE(lgd2.account_class,
2405                                                'UNEARN','REV',
2406                                                lgd2.account_class),
2407                                         'REV',       ctl.revenue_amount,
2408                                         'SUSPENSE',  ctl.extended_amount -
2409                                                      ctl.revenue_amount,
2410                                         ctl.extended_amount)
2411                              )
2412                             ),  /* entered amount */
2413                NVL(lgd.acctd_amount, 0) -
2414                  (
2415                    SUM(lgd2.acctd_amount) -
2416                    (
2417                      DECODE(lgd.gl_date,
2418                             rec1.gl_date, 1,
2419                             0) *
2420                      DECODE(p_base_mau,
2421                          NULL, ROUND(DECODE(DECODE(lgd2.account_class,
2422                                                    'UNEARN','REV',
2423                                                    lgd2.account_class),
2424                                             'REV',       ctl.revenue_amount,
2425                                             'SUSPENSE',  ctl.extended_amount -
2426                                                          ctl.revenue_amount,
2427                                             ctl.extended_amount) *
2428                                      NVL(ct.exchange_rate,1),
2429                                      p_base_precision ),
2430                                ROUND( (DECODE(DECODE(lgd2.account_class,
2431                                                      'UNEARN','REV',
2432                                                      lgd2.account_class),
2433                                             'REV',       ctl.revenue_amount,
2434                                             'SUSPENSE',  ctl.extended_amount -
2435                                                          ctl.revenue_amount,
2436                                             ctl.extended_amount) *
2437                                        NVL(ct.exchange_rate,1)
2438                                       ) / p_base_mau
2439                                     ) * p_base_mau
2440                         )
2441                    )
2442                  )              /* accounted amount */
2443                  FROM
2444                           ra_cust_trx_line_gl_dist lgd2,
2445                           ra_customer_trx_lines ctl,
2446                           ra_customer_trx ct,
2447                           ra_cust_trx_line_gl_dist rec1
2448                  WHERE
2449                           rec1.customer_trx_id      = lgd.customer_trx_id
2450                  AND      rec1.account_class        = 'REC'
2451                  AND      rec1.latest_rec_flag      = 'Y'
2452                  AND      ct.customer_trx_id        = rec1.customer_trx_id
2453                  AND      ctl.customer_trx_id       = ct.customer_trx_id
2454                  AND      ctl.customer_trx_line_id  = lgd.customer_trx_line_id
2455                  AND      lgd2.customer_trx_line_id = lgd.customer_trx_line_id
2456                  AND      lgd2.account_class        = lgd.account_class
2457                  AND      lgd2.account_set_flag     = 'N'
2458                  AND      lgd2.request_id = g_autoinv_request_id
2459                  AND      NVL(lgd2.gl_date, to_date( 2415021, 'J') )  =
2460                              NVL(lgd.gl_date, to_date( 2415021, 'J') )
2461                  GROUP BY
2462                           ctl.customer_trx_line_id,
2463                           DECODE(lgd2.account_class,'UNEARN','REV',
2464                                  lgd2.account_class),
2465                           rec1.gl_date,
2466                           ctl.extended_amount,
2467                           ctl.revenue_amount,
2468                           ct.exchange_rate
2469        ),
2470        percent =
2471        (SELECT /*+ index(LGD4 RA_CUST_TRX_LINE_GL_DIST_N10) */
2472                   DECODE(lgd.account_class || lgd.account_set_flag,
2473                          'SUSPENSEN', lgd.percent,
2474                          'UNBILLN', lgd.percent,
2475                          'UNEARNN', lgd.percent,
2476                          NVL(lgd.percent, 0) -
2477                                (
2478                                  SUM(NVL(lgd4.percent, 0))
2479                                  - DECODE(rec2.gl_date,
2480                                           NVL(lgd.gl_date, rec2.gl_date),
2481                                           100, 0)
2482                                )
2483                         )  /* percent */
2484         FROM
2485                   ra_cust_trx_line_gl_dist lgd4,
2486                   ra_cust_trx_line_gl_dist rec2
2487         WHERE
2488                   rec2.customer_trx_id      = lgd.customer_trx_id
2489         AND       rec2.account_class        = 'REC'
2490         AND       rec2.latest_rec_flag      = 'Y'
2491         AND       lgd4.customer_trx_line_id = lgd.customer_trx_line_id
2492         AND       lgd4.account_set_flag     = lgd.account_set_flag
2493         AND       DECODE(lgd4.account_set_flag,
2494                          'Y', lgd4.account_class,
2495                          lgd.account_class) = lgd.account_class
2496         AND       NVL(lgd4.gl_date, to_date( 2415021, 'J') )  =
2497                      NVL(lgd.gl_date, to_date( 2415021, 'J') )
2498         AND       lgd4.request_id = g_autoinv_request_id
2499         GROUP BY
2500                   rec2.gl_date,
2501                   lgd.gl_date
2502        ),
2503 last_updated_by = arp_global.last_updated_by,       /* Bug 2089972 */
2504 last_update_date = sysdate
2505 WHERE cust_trx_line_gl_dist_id  IN
2506        (SELECT /*+ leading(T,LGD3,REC3,CTL)
2507 	           use_hash(CTL) index(CTL RA_CUSTOMER_TRX_LINES_N4)
2508 	           index(LGD3 RA_CUST_TRX_LINE_GL_DIST_N6)
2509 	           index(REC3 RA_CUST_TRX_LINE_GL_DIST_N6) */
2510                MIN(DECODE(lgd3.gl_posted_date,
2511                           NULL, lgd3.cust_trx_line_gl_dist_id,
2512                           NULL) )
2513         FROM
2514                ra_customer_trx_lines ctl,
2515                ra_cust_trx_line_gl_dist lgd3,
2516                ra_cust_trx_line_gl_dist rec3,
2517                ra_customer_trx t
2518         WHERE
2519                t.customer_trx_id        = p_customer_trx_id
2520         AND    rec3.customer_trx_id     = t.customer_trx_id
2521         AND    rec3.account_class       = 'REC'
2522         AND    rec3.latest_rec_flag     = 'Y'
2523         AND    lgd3.customer_trx_id     = t.customer_trx_id
2524         AND    lgd3.account_set_flag    = 'N'
2525         AND    ctl.customer_trx_line_id = lgd3.customer_trx_line_id
2526         AND    (
2527                   ctl.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2528                 OR
2529                   (ctl.line_type = 'LINE' AND ctl.accounting_rule_id IS NULL)
2530                )
2531         AND    ctl.request_id = g_autoinv_request_id
2532         AND    ctl.customer_trx_id = p_customer_trx_id
2533         AND    NVL(t.previous_customer_trx_id, -1) =
2534                 DECODE(p_trx_class_to_process,
2535                        'INV', -1,
2536                        'REGULAR_CM', t.previous_customer_trx_id,
2537                        NVL(t.previous_customer_trx_id, -1) )
2538         GROUP BY
2539                  ctl.customer_trx_line_id,
2540                  DECODE(lgd3.account_class,'UNEARN','REV',lgd3.account_class),
2541                  lgd3.gl_date,
2542                  rec3.gl_date,
2543                  ctl.extended_amount,
2544                  ctl.revenue_amount,
2545                  t.exchange_rate
2546         HAVING (
2547                   SUM(NVL(lgd3.amount, 0))
2548                             <> DECODE(DECODE(lgd3.account_class,
2549                                              'UNEARN','REV',lgd3.account_class),
2550                                      'REV',       ctl.revenue_amount,
2551                                      'SUSPENSE',  ctl.extended_amount -
2552                                                          ctl.revenue_amount,
2553                                       ctl.extended_amount) *
2554                                DECODE(lgd3.gl_date,
2555                                       rec3.gl_date, 1,
2556                                       0)
2557                 OR
2558                   SUM(NVL(lgd3.acctd_amount, 0)) <>
2559                   DECODE(lgd3.gl_date,
2560                          rec3.gl_date, 1,
2561                          0) *
2562                   DECODE(p_base_mau,
2563                          NULL, ROUND(DECODE(DECODE(lgd3.account_class,
2564                                                    'UNEARN','REV',
2565                                                    lgd3.account_class),
2566                                             'REV',       ctl.revenue_amount,
2567                                             'SUSPENSE',  ctl.extended_amount -
2568                                                          ctl.revenue_amount,
2569                                             ctl.extended_amount) *
2570                                      NVL(t.exchange_rate,1),
2571                                      p_base_precision),
2572                          ROUND( (DECODE(DECODE(lgd3.account_class,
2573                                                'UNEARN','REV',
2574                                                lgd3.account_class),
2575                                             'REV',       ctl.revenue_amount,
2576                                             'SUSPENSE',  ctl.extended_amount -
2577                                                          ctl.revenue_amount,
2578                                             ctl.extended_amount) *
2579                                        NVL(t.exchange_rate,1)
2580                                 ) / p_base_mau
2581                               ) * p_base_mau
2582                         )
2583                )
2584        UNION
2585        SELECT  /*+ leading(CTL2 LGD5,REC5)
2586 	           use_hash(LGD5) index(CTL2 RA_CUSTOMER_TRX_LINES_N4)
2587 		   index(REC5 RA_CUST_TRX_LINE_GL_DIST_N6)
2588 		   index(LGD5 RA_CUST_TRX_LINE_GL_DIST_N6) */
2589                TO_NUMBER(
2590                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
2591                                     lgd5.account_set_flag,
2592                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
2593                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
2594                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
2595                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
2596                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
2597                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
2598                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
2599                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
2600                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
2601                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
2602                                      NULL
2603                                    )
2604                             )
2605                        )
2606        FROM
2607               ra_cust_trx_line_gl_dist rec5,
2608               ra_cust_trx_line_gl_dist lgd5,
2609               ra_customer_trx_lines ctl2
2610        WHERE
2611               ctl2.customer_trx_id      = p_customer_trx_id
2612        AND    ctl2.request_id           = g_autoinv_request_id
2613        AND    rec5.customer_trx_id      = lgd5.customer_trx_id
2614        AND    rec5.account_class        = 'REC'
2615        AND    rec5.latest_rec_flag      = 'Y'
2616        AND    lgd5.customer_trx_line_id = ctl2.customer_trx_line_id
2617        AND    lgd5.customer_trx_id      = p_customer_trx_id
2618        AND    (
2619                 ctl2.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2620                 OR
2621                 (ctl2.line_type = 'LINE'   AND
2622                  (ctl2.accounting_rule_id  IS NULL OR
2623                      lgd5.account_set_flag = 'Y')
2624                 )
2625               )
2626        GROUP BY
2627                 lgd5.customer_trx_line_id,
2628                 lgd5.gl_date,
2629                 rec5.gl_date,
2630                 lgd5.account_set_flag,
2631                 DECODE(lgd5.account_set_flag,
2632                        'N', NULL,
2633                        lgd5.account_class)
2634        HAVING SUM(NVL(lgd5.percent, 0)) <>
2635               DECODE( NVL(lgd5.gl_date, rec5.gl_date),
2636                       rec5.gl_date, 100,
2637                       0)
2638        );
2639 
2640       ELSE
2641          /* original version (used by forms and Rev Rec */
2642 
2643          /* 9160123 - simplied where clause for this statement */
2644 
2645 UPDATE ra_cust_trx_line_gl_dist lgd
2646 SET    (amount, acctd_amount)  =
2647        (SELECT NVL(lgd.amount, 0) -
2648                             (
2649                              SUM(lgd2.amount) -
2650                              (
2651                                  DECODE(lgd.gl_date,
2652                                         rec1.gl_date, 1,
2653                                         0) *
2654                                  DECODE(DECODE(lgd2.account_class,
2655                                                'UNEARN','REV',
2656                                                lgd2.account_class),
2657                                         'REV',       ctl.revenue_amount,
2658                                         'SUSPENSE',  ctl.extended_amount -
2659                                                      ctl.revenue_amount,
2660                                         ctl.extended_amount)
2661                              )
2662                             ),  /* entered amount */
2663                NVL(lgd.acctd_amount, 0) -
2664                  (
2665                    SUM(lgd2.acctd_amount) -
2666                    (
2667                      DECODE(lgd.gl_date,
2668                             rec1.gl_date, 1,
2669                             0) *
2670                      DECODE(p_base_mau,
2671                          NULL, ROUND(DECODE(DECODE(lgd2.account_class,
2672                                                    'UNEARN','REV',
2673                                                    lgd2.account_class),
2674                                             'REV',       ctl.revenue_amount,
2675                                             'SUSPENSE',  ctl.extended_amount -
2676                                                          ctl.revenue_amount,
2677                                             ctl.extended_amount) *
2678                                      NVL(ct.exchange_rate,1),
2679                                      p_base_precision ),
2680                                ROUND( (DECODE(DECODE(lgd2.account_class,
2681                                                      'UNEARN','REV',
2682                                                      lgd2.account_class),
2683                                             'REV',       ctl.revenue_amount,
2684                                             'SUSPENSE',  ctl.extended_amount -
2685                                                          ctl.revenue_amount,
2686                                             ctl.extended_amount) *
2687                                        NVL(ct.exchange_rate,1)
2688                                       ) / p_base_mau
2689                                     ) * p_base_mau
2690                         )
2691                    )
2692                  )              /* accounted amount */
2693                  FROM
2694                           ra_cust_trx_line_gl_dist lgd2,
2695                           ra_customer_trx_lines ctl,
2696                           ra_customer_trx ct,
2697                           ra_cust_trx_line_gl_dist rec1
2698                  WHERE
2699                           rec1.customer_trx_id      = lgd.customer_trx_id
2700                  AND      rec1.account_class        = 'REC'
2701                  AND      rec1.latest_rec_flag      = 'Y'
2702                  AND      ct.customer_trx_id        = rec1.customer_trx_id
2703                  AND      ctl.customer_trx_id       = ct.customer_trx_id
2704                  AND      ctl.customer_trx_line_id  = lgd.customer_trx_line_id
2705                  AND      lgd2.customer_trx_line_id = lgd.customer_trx_line_id
2706                  AND      lgd2.account_class        = lgd.account_class
2707                  AND      lgd2.account_set_flag     = 'N'
2708                  AND      NVL(lgd2.gl_date, to_date( 2415021, 'J') )  =
2709                              NVL(lgd.gl_date, to_date( 2415021, 'J') )
2710                  GROUP BY
2711                           ctl.customer_trx_line_id,
2712                           DECODE(lgd2.account_class,'UNEARN','REV',
2713                                  lgd2.account_class),
2714                           rec1.gl_date,
2715                           ctl.extended_amount,
2716                           ctl.revenue_amount,
2717                           ct.exchange_rate
2718        ),
2719        percent =
2720        (SELECT    DECODE(lgd.account_class || lgd.account_set_flag,
2721                          'SUSPENSEN', lgd.percent,
2722                          'UNBILLN', lgd.percent,
2723                          'UNEARNN', lgd.percent,
2724                          NVL(lgd.percent, 0) -
2725                                (
2726                                  SUM(NVL(lgd4.percent, 0))
2727                                  - DECODE(rec2.gl_date,
2728                                           NVL(lgd.gl_date, rec2.gl_date),
2729                                           100, 0)
2730                                )
2731                         )  /* percent */
2732         FROM
2733                   ra_cust_trx_line_gl_dist lgd4,
2734                   ra_cust_trx_line_gl_dist rec2
2735         WHERE
2736                   rec2.customer_trx_id      = lgd.customer_trx_id
2737         AND       rec2.account_class        = 'REC'
2738         AND       rec2.latest_rec_flag      = 'Y'
2739         AND       lgd4.customer_trx_line_id = lgd.customer_trx_line_id
2740         AND       lgd4.account_set_flag     = lgd.account_set_flag
2741         AND       DECODE(lgd4.account_set_flag,
2742                          'Y', lgd4.account_class,
2743                          lgd.account_class) = lgd.account_class
2744         AND       NVL(lgd4.gl_date, to_date( 2415021, 'J') )  =
2745                      NVL(lgd.gl_date, to_date( 2415021, 'J') )
2746         GROUP BY
2747                   rec2.gl_date,
2748                   lgd.gl_date
2749        ),
2750 last_updated_by = arp_global.last_updated_by,       /* Bug 2089972 */
2751 last_update_date = sysdate
2752 WHERE cust_trx_line_gl_dist_id  IN
2753        (SELECT MIN(DECODE(lgd3.gl_posted_date,
2754                           NULL, lgd3.cust_trx_line_gl_dist_id,
2755                           NULL) )
2756         FROM
2757                ra_customer_trx_lines ctl,
2758                ra_cust_trx_line_gl_dist lgd3,
2759                ra_cust_trx_line_gl_dist rec3,
2760                ra_customer_trx t
2761         WHERE
2762                t.customer_trx_id        = p_customer_trx_id
2763         AND    rec3.customer_trx_id     = t.customer_trx_id
2764         AND    rec3.account_class       = 'REC'
2765         AND    rec3.latest_rec_flag     = 'Y'
2766         AND    lgd3.customer_trx_id     = t.customer_trx_id
2767         AND    lgd3.account_set_flag    = 'N'
2768         AND    ctl.customer_trx_line_id = lgd3.customer_trx_line_id
2769         AND    (
2770                   ctl.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2771                 OR
2772                   (ctl.line_type = 'LINE' AND ctl.accounting_rule_id IS NULL)
2773                )
2774         AND    NVL(t.previous_customer_trx_id, -1) =
2775                 DECODE(p_trx_class_to_process,
2776                        'INV', -1,
2777                        'REGULAR_CM', t.previous_customer_trx_id,
2778                        NVL(t.previous_customer_trx_id, -1) )
2779         GROUP BY
2780                  ctl.customer_trx_line_id,
2781                  DECODE(lgd3.account_class,'UNEARN','REV',lgd3.account_class),
2782                  lgd3.gl_date,
2783                  rec3.gl_date,
2784                  ctl.extended_amount,
2785                  ctl.revenue_amount,
2786                  t.exchange_rate
2787         HAVING (
2788                   SUM(NVL(lgd3.amount, 0))
2789                             <> DECODE(DECODE(lgd3.account_class,
2790                                              'UNEARN','REV',lgd3.account_class),
2791                                      'REV',       ctl.revenue_amount,
2792                                      'SUSPENSE',  ctl.extended_amount -
2793                                                          ctl.revenue_amount,
2794                                       ctl.extended_amount) *
2795                                DECODE(lgd3.gl_date,
2796                                       rec3.gl_date, 1,
2797                                       0)
2798                 OR
2799                   SUM(NVL(lgd3.acctd_amount, 0)) <>
2800                   DECODE(lgd3.gl_date,
2801                          rec3.gl_date, 1,
2802                          0) *
2803                   DECODE(p_base_mau,
2804                          NULL, ROUND(DECODE(DECODE(lgd3.account_class,
2805                                                    'UNEARN','REV',
2806                                                    lgd3.account_class),
2807                                             'REV',       ctl.revenue_amount,
2808                                             'SUSPENSE',  ctl.extended_amount -
2809                                                          ctl.revenue_amount,
2810                                             ctl.extended_amount) *
2811                                      NVL(t.exchange_rate,1),
2812                                      p_base_precision),
2813                          ROUND( (DECODE(DECODE(lgd3.account_class,
2814                                                'UNEARN','REV',
2815                                                lgd3.account_class),
2816                                             'REV',       ctl.revenue_amount,
2817                                             'SUSPENSE',  ctl.extended_amount -
2818                                                          ctl.revenue_amount,
2819                                             ctl.extended_amount) *
2820                                        NVL(t.exchange_rate,1)
2821                                 ) / p_base_mau
2822                               ) * p_base_mau
2823                         )
2824                )
2825        UNION
2826        SELECT /*+ index( REC5 RA_CUST_TRX_LINE_GL_DIST_N6) */
2827               TO_NUMBER(
2828                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
2829                                     lgd5.account_set_flag,
2830                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
2831                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
2832                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
2833                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
2834                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
2835                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
2836                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
2837                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
2838                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
2839                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
2840                                      NULL
2841                                    )
2842                             )
2843                        )
2844        FROM
2845               ra_cust_trx_line_gl_dist rec5,
2846               ra_cust_trx_line_gl_dist lgd5,
2847               ra_customer_trx_lines ctl2
2848        WHERE
2849               rec5.customer_trx_id      = p_customer_trx_id
2850        AND    rec5.account_class        = 'REC'
2851        AND    rec5.latest_rec_flag      = 'Y'
2852        AND    rec5.customer_trx_id      = ctl2.customer_trx_id
2853        AND    ctl2.customer_trx_line_id = lgd5.customer_trx_line_id
2854        AND    lgd5.account_set_flag =
2855                   DECODE(ctl2.line_type, 'LINE',
2856                      DECODE(ctl2.accounting_rule_id, NULL, 'N', 'Y'),
2857                             lgd5.account_set_flag)
2858        GROUP BY
2859                 lgd5.customer_trx_line_id,
2860                 lgd5.gl_date,
2861                 rec5.gl_date,
2862                 lgd5.account_set_flag,
2863                 DECODE(lgd5.account_set_flag,
2864                        'N', NULL,
2865                        lgd5.account_class)
2866        HAVING SUM(NVL(lgd5.percent, 0)) <>
2867               DECODE( NVL(lgd5.gl_date, rec5.gl_date),
2868                       rec5.gl_date, 100,
2869                       0)
2870        );
2871 
2872       END IF; /* g_autoinv case */
2873    END IF; /* customer_trx_id case */
2874 
2875    IF (p_customer_trx_line_id IS NOT NULL)
2876    THEN
2877 
2878 UPDATE ra_cust_trx_line_gl_dist lgd
2879 SET    (amount, acctd_amount)  =
2880        (SELECT NVL(lgd.amount, 0) -
2881                             (
2882                              SUM(lgd2.amount) -
2883                              (
2884                                  DECODE(lgd.gl_date,
2885                                         rec1.gl_date, 1,
2886                                         0) *
2887                                  DECODE(DECODE(lgd2.account_class,
2888                                                'UNEARN','REV',
2889                                                lgd2.account_class),
2890                                         'REV',       ctl.revenue_amount,
2891                                         'SUSPENSE',  ctl.extended_amount -
2892                                                      ctl.revenue_amount,
2893                                         ctl.extended_amount)
2894                              )
2895                             ),  /* entered amount */
2896                NVL(lgd.acctd_amount, 0) -
2897                  (
2898                    SUM(lgd2.acctd_amount) -
2899                    (
2900                      DECODE(lgd.gl_date,
2901                             rec1.gl_date, 1,
2902                             0) *
2903                      DECODE(p_base_mau,
2904                          NULL, ROUND(DECODE(DECODE(lgd2.account_class,
2905                                                    'UNEARN','REV',
2906                                                    lgd2.account_class),
2907                                             'REV',       ctl.revenue_amount,
2908                                             'SUSPENSE',  ctl.extended_amount -
2909                                                          ctl.revenue_amount,
2910                                             ctl.extended_amount) *
2911                                      NVL(ct.exchange_rate,1),
2912                                      p_base_precision ),
2913                                ROUND( (DECODE(DECODE(lgd2.account_class,
2914                                                      'UNEARN','REV',
2915                                                      lgd2.account_class),
2916                                              'REV',       ctl.revenue_amount,
2917                                              'SUSPENSE',  ctl.extended_amount -
2918                                                           ctl.revenue_amount,
2919                                              ctl.extended_amount) *
2920                                        NVL(ct.exchange_rate,1)
2921                                       ) / p_base_mau
2922                                     ) * p_base_mau
2923                         )
2924                    )
2925                  )              /* accounted amount */
2926                  FROM
2927                           ra_cust_trx_line_gl_dist lgd2,
2928                           ra_customer_trx_lines ctl,
2929                           ra_customer_trx ct,
2930                           ra_cust_trx_line_gl_dist rec1
2931                  WHERE
2932                           rec1.customer_trx_id      = lgd.customer_trx_id
2933                  and      rec1.account_class        = 'REC'
2934                  and      rec1.latest_rec_flag      = 'Y'
2935                  and      ct.customer_trx_id        = rec1.customer_trx_id
2936                  and      ctl.customer_trx_id       = ct.customer_trx_id
2937                  and      ctl.customer_trx_line_id  = lgd.customer_trx_line_id
2938                  and      lgd2.customer_trx_line_id = lgd.customer_trx_line_id
2939                  and      lgd2.account_class        = lgd.account_class
2940                  and      lgd2.account_set_flag     = 'N'
2941                  and      NVL(lgd2.gl_date, to_date( 2415021, 'J') )  =
2942                              NVL(lgd.gl_date, to_date( 2415021, 'J') )
2943                  GROUP BY
2944                           ctl.customer_trx_line_id,
2945                           DECODE(lgd2.account_class,'UNEARN','REV',
2946                                  lgd2.account_class),
2947                           rec1.gl_date,
2948                           ctl.extended_amount,
2949                           ctl.revenue_amount,
2950                           ct.exchange_rate
2951        ),
2952        percent =
2953        (SELECT    DECODE(lgd.account_class || lgd.account_set_flag,
2954                          'SUSPENSEN', lgd.percent,
2955                          'UNBILLN', lgd.percent,
2956                          'UNEARNN', lgd.percent,
2957                          NVL(lgd.percent, 0) -
2958                                (
2959                                  SUM(NVL(lgd4.percent, 0))
2960                                  - DECODE(rec2.gl_date,
2961                                           NVL(lgd.gl_date, rec2.gl_date),
2962                                           100, 0)
2963                                )
2964                         )  /* percent */
2965         FROM
2966                   ra_cust_trx_line_gl_dist lgd4,
2967                   ra_cust_trx_line_gl_dist rec2
2968         WHERE
2969                   rec2.customer_trx_id      = lgd.customer_trx_id
2970         AND       rec2.account_class        = 'REC'
2971         AND       rec2.latest_rec_flag      = 'Y'
2972         AND       lgd4.customer_trx_line_id = lgd.customer_trx_line_id
2973         AND       lgd4.account_set_flag     = lgd.account_set_flag
2974         AND       DECODE(lgd4.account_set_flag,
2975                          'Y', lgd4.account_class,
2976                          lgd.account_class) = lgd.account_class
2977         AND       NVL(lgd4.gl_date, to_date( 2415021, 'J') )  =
2978                      NVL(lgd.gl_date, to_date( 2415021, 'J') )
2979         GROUP BY
2980                   rec2.gl_date,
2981                   lgd.gl_date
2982        ),
2983 last_updated_by = arp_global.last_updated_by,    /* Bug 2089972 */
2984 last_update_date = sysdate
2985  WHERE cust_trx_line_gl_dist_id  IN
2986        (SELECT MIN(DECODE(lgd3.gl_posted_date,
2987                           NULL, lgd3.cust_trx_line_gl_dist_id,
2988                           NULL) )
2989         FROM
2990                ra_cust_trx_line_gl_dist lgd3,
2991                ra_cust_trx_line_gl_dist rec3,
2992                ra_customer_trx t,
2993                ra_customer_trx_lines ctl
2994         WHERE
2995                ctl.customer_trx_line_id  = p_customer_trx_line_id
2996         AND    t.customer_trx_id         = ctl.customer_trx_id
2997         AND    rec3.customer_trx_id      = t.customer_trx_id
2998         AND    rec3.account_class        = 'REC'
2999         AND    rec3.latest_rec_flag      = 'Y'
3000         AND    (
3001                   ctl.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
3002                 OR
3003                   (ctl.line_type = 'LINE' AND ctl.accounting_rule_id IS NULL)
3004                )
3005         AND    lgd3.customer_trx_line_id = ctl.customer_trx_line_id
3006         AND    lgd3.account_set_flag     = 'N'
3007         AND    NVL(t.previous_customer_trx_id, -1) =
3008                 DECODE(p_trx_class_to_process,
3009                        'INV',        -1,
3010                        'REGULAR_CM', t.previous_customer_trx_id,
3011                        NVL(t.previous_customer_trx_id, -1) )
3012         GROUP BY
3013                  ctl.customer_trx_line_id,
3014                  DECODE(lgd3.account_class,'UNEARN','REV',lgd3.account_class),
3015                  lgd3.gl_date,
3016                  rec3.gl_date,
3017                  ctl.extended_amount,
3018                  ctl.revenue_amount,
3019                  t.exchange_rate
3020         HAVING (
3021                   SUM(NVL(lgd3.amount, 0))
3022                             <> DECODE(DECODE(lgd3.account_class,
3023                                              'UNEARN','REV',lgd3.account_class),
3024                                       'REV',       ctl.revenue_amount,
3025                                       'SUSPENSE',  ctl.extended_amount -
3026                                                    ctl.revenue_amount,
3027                                       ctl.extended_amount) *
3028                                DECODE(lgd3.gl_date,
3029                                       rec3.gl_date, 1,
3030                                       0)
3031                 OR
3032                   SUM(NVL(lgd3.acctd_amount, 0)) <>
3033                   DECODE(lgd3.gl_date,
3034                          rec3.gl_date, 1,
3035                          0) *
3036                   DECODE(p_base_mau,
3037                          NULL, ROUND(DECODE(DECODE(lgd3.account_class,
3038                                                    'UNEARN','REV',
3039                                                    lgd3.account_class),
3040                                             'REV',       ctl.revenue_amount,
3041                                             'SUSPENSE',  ctl.extended_amount -
3042                                                          ctl.revenue_amount,
3043                                             ctl.extended_amount) *
3044                                      NVL(t.exchange_rate,1),
3045                                      p_base_precision),
3046                          ROUND( (DECODE(DECODE(lgd3.account_class,
3047                                                'UNEARN','REV',
3048                                                lgd3.account_class),
3049                                             'REV',       ctl.revenue_amount,
3050                                             'SUSPENSE',  ctl.extended_amount -
3051                                                          ctl.revenue_amount,
3052                                             ctl.extended_amount) *
3053                                        NVL(t.exchange_rate,1)
3054                                 ) / p_base_mau
3055                               ) * p_base_mau
3056                         )
3057                )
3058        UNION
3059        SELECT TO_NUMBER(
3060                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
3061                                     lgd5.account_set_flag,
3062                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
3063                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
3064                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
3065                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
3066                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
3067                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
3068                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
3069                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
3070                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
3071                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
3072                                      NULL) )
3073                        )
3074        FROM
3075               ra_cust_trx_line_gl_dist lgd5,
3076               ra_cust_trx_line_gl_dist rec5,
3077               ra_customer_trx_lines ctl2
3078        WHERE
3079               ctl2.customer_trx_line_id = p_customer_trx_line_id
3080        AND    rec5.customer_trx_id      = lgd5.customer_trx_id
3081        AND    rec5.account_class        = 'REC'
3082        AND    rec5.latest_rec_flag      = 'Y'
3083        AND    lgd5.customer_trx_line_id = ctl2.customer_trx_line_id
3084        AND    (
3085                   ctl2.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
3086                 OR
3087                   (ctl2.line_type = 'LINE'   AND
3088                     (ctl2.accounting_rule_id IS NULL OR
3089                      lgd5.account_set_flag   = 'Y')
3090                   )
3091                )
3092        GROUP BY
3093                 lgd5.customer_trx_line_id,
3094                 lgd5.gl_date,
3095                 rec5.gl_date,
3096                 lgd5.account_set_flag,
3097                 DECODE(lgd5.account_set_flag,
3098                        'N', NULL,
3099                        lgd5.account_class)
3100        HAVING SUM(NVL(lgd5.percent, 0)) <>
3101               DECODE( NVL(lgd5.gl_date, rec5.gl_date),
3102                       rec5.gl_date, 100,
3103                       0)
3104        );
3105 
3106 
3107 
3108    END IF; /* customer_trx_line_id case */
3109 
3110    l_count := sql%rowcount;
3111 
3112    IF PG_DEBUG in ('Y', 'C') THEN
3113       arp_standard.debug(
3114           'Rows Processed: '||
3115           l_count);
3116    END IF;
3117 
3118    p_rows_processed := p_rows_processed + l_count;
3119 
3120    IF PG_DEBUG in ('Y', 'C') THEN
3121       arp_standard.debug( 'arp_rounding.correct_nonrule_line_records()- ' ||
3122                       TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3123    END IF;
3124 
3125   /* MRC Processing */
3126   IF PG_DEBUG in ('Y', 'C') THEN
3127      arp_standard.debug('doing rounding for MRC if necessary');
3128   END IF;
3129   ar_mrc_engine2.mrc_correct_rounding(
3130                    'CORRECT_NONRULE_LINE_RECORDS',
3131                    P_REQUEST_ID,
3132                    P_CUSTOMER_TRX_ID,
3133                    P_CUSTOMER_TRX_LINE_ID,
3134                    P_TRX_CLASS_TO_PROCESS
3135                   );
3136 
3137   RETURN( iTRUE );
3138  EXCEPTION
3139   WHEN others THEN
3140     p_error_message := SQLERRM;
3141     IF PG_DEBUG in ('Y', 'C') THEN
3142        arp_standard.debug('EXCEPTION:  arp_rounding.correct_nonrule_line_records failed()- '||
3143                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3144     END IF;
3145     RETURN(iFALSE);
3146 
3147 END correct_nonrule_line_records;
3148 
3149 /* Bug 2576253 - removed logic for FUNCTION correct_rule_records */
3150 
3151 /*-------------------------------------------------------------------------+
3152  | PRIVATE FUNCTION                                                        |
3153  |   correct_rule_records_by_line()                                        |
3154  |                                                                         |
3155  | DESCRIPTION                                                             |
3156  |   This function corrects errors in lines that use rules.                |
3157  |   It is a complete (from the ground up) rewrite of the logic in
3158  |   correct_rule_records.  The function correct_rule_records was designed
3159  |   to compensate for partially generated invoices (a norm in 10.7 and
3160  |   prior versions).  Accomodating that behavior resulted in very complex
3161  |   (and slow) logic.
3162  |
3163  |   The new function is broken into two pieces and relies upon bulk updates
3164  |   to update multiple rows at one time.  The first component is the
3165  |   driving cursor that identifies the specific lines that require rounding
3166  |   (customer_trx_line_id, account_class, amount, acctd_amount, and percent).
3167  |   The amount, acctd_amount, and percent are all DELTA values (the amount of
3168  |   rounding required.  To avoid problems with partially generated CMs (via
3169  |   ARTECMMB.pls, this logic will not round if the autorule_complete_flag is
3170  |   not null.  To avoid issues with old transactions, I now skip lines
3171  |   that have no unposted distributions.
3172  |
3173  |   The second component is an update statement that is fed by a second
3174  |   (included) subquery that identifies the specific gl_dist lines to update
3175  |   for each customer_trx_line_id.  This routine will always update the
3176  |   gl_dist line with the latest gl_date, highest amount, and if the prior
3177  |   two columns are the same, max(gl_dist_id).  This means that gl_dist_id
3178  |   is now only the tiebreaker, not the driving column.  For bug 2495595,
3179  |   we now only consider rows with posting_control_id = -3 to be recipients
3180  |   of rounding amounts.
3181  |
3182  |   Another noteworthy feature as of bug 2390821 is that we now round
3183  |   the REV, UNEARN (rec offset), and UNEARN (rev offset) separately.
3184  |   This was necessary because the original logic assummed (incorrectly)
3185  |   that the rec_offset UNEARN or UNBILL rows would be in balance naturally.
3186  |
3187  |   In bug 2480898, 2493896, and 2497841, we learned that older transactions
3188  |   that do not have rec_offset_flag set will be corrupted if they pass
3189  |   through the rounding logic again.  This happens if users manipulate
3190  |   the distributions of a completed and posted rule-based transaction.
3191  |   So, we now watch for transactions that do not have the rec_offset_flag
3192  |   set and set them where possible.  Will will not round a transaction line
3193  |   unless there is a rec_offset_flag=Y row for that line.
3194  |
3195  |   In bug 2535023 (see bug 2543675), we discovered that older versions of
3196  |   autoaccounting and unexpected behavior in ARXTWMAI can lead to situations
3197  |   where distributions are out of balance in interim (not last) period(s).
3198  |   When rounding fires, it would correct (but in last period) creating out
3199  |   of balance entries in two or more periods.  To prevent this, we included
3200  |   a new procedure called true_lines_by_gl_date to push rows back in synch
3201  |   before we actually round them for the line in total.
3202  |
3203  |   In bug 2449955, we figured out that we were not handling deferred
3204  |   lines on ARREARS invoices properly. We should treat them as if they
3205  |   were not deferred at all (just like conventional non-deferred rules).
3206  |
3207  |   In bugs 6325023 and 6473284, we learned that SLA will not post
3208  |   distributions with entered and acctd amounts having opposite signs.
3209  |   Since this is possible for transactions that are not in functional
3210  |   currency with very small line amounts (<.20).  To resolve that,
3211  |   we added logic to detect these situations and to insert a separate
3212  |   distributions to record amount and percent corrections and another
3213  |   distribution if the acctd_amount correction is the wrong sign.
3214  |
3215  |   For example, if the rounding correction would reverse the sign of
3216  |   the acctd_amount, then we will insert a separate distribution to
3217  |   record that correction.  However, if the entered and acctd corrections
3218  |   are themselves of opposite signs, then we'll insert one positive
3219  |   and a separate one with zero amount and negative acctd_amount.
3220  |
3221  |   This matrix helps explain what we round each line (by account_class)
3222  |   to:
3223  |
3224  |   CLASS  ROF  DEF   RULE   RESULT    NOTES
3225  |   REV    N    N     -2/-3  rev_amt
3226  |   REV    N    Y     -2     0         form adjustments
3227  |   REV    N    Y     -3     rev_amt
3228  |   UE     N    N     -2/-3  rev_amt*-1
3229  |   UE     Y    N     -2/-3  rev_amt
3230  |   UE     N    Y     -2     0         form adjustments
3231  |   UE     Y    Y     -2/-3  rev_amt
3232  |   UE     N    Y     -3     rev_amt   overrides deferred rules
3233  |
3234  | REQUIRES                                                                |
3235  |   All IN parameters                                                     |
3236  |                                                                         |
3237  | RETURNS                                                                 |
3238  |   TRUE  if no errors occur                                              |
3239  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
3240  |                                                                         |
3241  | NOTES                                                                   |
3242  |                                                                         |
3243  | EXAMPLE                                                                 |
3244  |                                                                         |
3245  | MODIFICATION HISTORY                                                    |
3246  |
3247  |  Created by bug 2150541
3248  |
3249  |   06-JUN-2002   M Raymond  2398021   Restructured both select and update
3250  |                                      to accomodate rounding of the
3251  |                                      rec_offset_rows.                   |
3252  |   09-JUL-2002   M Raymond  2445800   Added a where clause to accomodate
3253  |                                      CMs against invoices that have been
3254  |                                      reversed and regenerated by RAM.
3255  |   31-JUL-2002   M Raymond  2487744   Modified logic for deferred rules
3256  |                                      to round CMs against deferred invoices.
3257  |   02-AUG-2002   M Raymond  2492345   Exclude model rows when determining
3258  |                                      the max gl_date
3259  |   03-AUG-2002   M Raymond  2497841   Test and (when necessary) set the
3260  |                                      rec_offset_flag
3261  |                                      Added parameter for suppressing
3262  |                                      rec_offset_flag on calls from
3263  |                                      revenue recognition.
3264  |   20-AUG-2002   M Raymond  2480852   Change handling of deferred rules
3265  |                                      and revenue adjustments.
3266  |   20-AUG-2002   M Raymond  2480852   Exclude posted rows from being
3267  |                                      recipients of rounding amounts.
3268  |   26-AUG-2002   M Raymond  2532648   Exclude posted rows from rounding
3269  |                                      completely.
3270  |   27-AUG-2002   M Raymond  2532648   Re-implemented skipping of lines
3271  |                                      bearing deferred rules.
3272  |   04-SEP-2002   M Raymond  2535023   Revised SELECT to carefully round
3273  |                                      form adjustments on deferred rule lines
3274  |                                      to zero instead of extended amount.
3275  |   05-SEP-2002   M Raymond  2535023   Added a separate private procedure
3276  |                                      called true_lines_by_gl_date.  Now
3277  |                                      calling this routine to make sure
3278  |                                      gl_dates in all periods balance before
3279  |                                      I round the line in total.
3280  |   10-SEP-2002   M Raymond  2559944   Not handling deferred lines for
3281  |                                      ARREARS invoices properly.  Revised
3282  |                                      CURSOR to properly ignore defers
3283  |                                      on ARREARS invoices.
3284  |   13-SEP-2002   M Raymond  2543576   Switched from extended_amount to
3285  |                                      revenue_amount.  This accomodates
3286  |                                      situations where suspense accounts are
3287  |                                      in use.  Just FYI, ext_amt = qty * prc
3288  |                                      and rev_amt can equal ext_amt unless
3289  |                                      the user passed a different ext_amt
3290  |                                      via autoinvoice and had clearing
3291  |                                      enabled.  The amt passed by user
3292  |                                      and used for line is stored in
3293  |                                      revenue_amount
3294  |   14-SEP-2002   M Raymond  2569870   Prevented RAM dists from being
3295  |                                      recipient of rounding (UPDATE).  Also
3296  |                                      changed SELECT to exclude rule-based
3297  |                                      lines when no rec_offset row exists.
3298  |   06-MAR-2003   M Raymond  2632863   Fixed rounding errors when dist in
3299  |                                      last period was of opposite sign
3300  |                                      ex: CM vs .2/12 invoice
3301  |   02-OCT-2003   M Raymond  3033850/3067588
3302  |                                      Modified code to execute three times
3303  |                                      for same, opposite, and zero rounding.
3304  |                                      Also removed sign subquery.
3305  |   04-MAY-2004   M Raymond  3605089   Added logic for SUSPENSE to this
3306  |                                      logic to round for salescredit
3307  |                                      splits.  later removed logic as
3308  |                                      it does not resolve issue at hand.
3309  |                                      See ARPLCREB.pls 115.64 if SUSPENSE
3310  |                                      rounding comes in conjunction with
3311  |                                      salescredits.
3312  |   06-OCT-2007   M Raymond  6325023/6473284 - Added logic to handle
3313  |                                      unusual rounding issues for
3314  |                                      acctd amounts.
3315  +-------------------------------------------------------------------------*/
3316 
3317 FUNCTION correct_rule_records_by_line(
3318 		P_REQUEST_ID           IN NUMBER,
3319                 P_CUSTOMER_TRX_ID      IN NUMBER,
3320                 P_ROWS_PROCESSED       IN OUT NOCOPY NUMBER,
3321                 P_ERROR_MESSAGE        OUT NOCOPY VARCHAR2,
3322                 P_BASE_PRECISION       IN NUMBER,
3323                 P_BASE_MAU             IN NUMBER,
3324                 P_TRX_CLASS_TO_PROCESS IN VARCHAR2,
3325                 P_CHECK_RULES_FLAG     IN VARCHAR2,
3326                 P_PERIOD_SET_NAME      IN OUT NOCOPY VARCHAR2,
3327                 P_FIX_REC_OFFSET       IN VARCHAR2 DEFAULT 'Y')
3328 
3329          RETURN NUMBER IS
3330 
3331   t_line_id       l_line_id_type;
3332   t_gl_id         l_line_id_type;
3333   t_round_amount  l_amount_type;
3334   t_round_percent l_percent_type;
3335   t_round_acctd   l_amount_type;
3336   t_account_class l_acct_class;
3337   t_rec_offset    l_rec_offset;
3338 
3339   l_rows_needing_rounding NUMBER;
3340   l_rows_rounded NUMBER := 0;
3341   l_rows_rounded_this_pass NUMBER := 0;
3342   l_phase NUMBER := 0;
3343 
3344   l_result NUMBER;
3345   /* Cursor for FINAL rounding
3346      Detects which customer_trx_line_ids require rounding
3347      and determines the amount, acctd_amount, and percent
3348      for each account_class */
3349 
3350   /* Dev note:  The EXISTS clause for rec_offset_flag (rof)
3351      was added as a precaution.  It has a noticable impact on
3352      the explain plan - so it may be necessary to remove it
3353      if performance becomes an issue in this code.  An alternative
3354      would be to put it in the UPDATE instead, thus limiting the number
3355      of times it gets called.*/
3356 
3357   CURSOR round_rows_by_trx(p_trx_id NUMBER,
3358                            p_base_mau NUMBER,
3359                            p_base_precision NUMBER) IS
3360   select l.customer_trx_line_id, g.account_class,
3361          /* AMOUNT LOGIC */
3362          (DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3363              DECODE(r.deferred_revenue_flag, 'Y',
3364                 DECODE(t.invoicing_rule_id, -2, 0, l.revenue_amount),
3365                l.revenue_amount))
3366           - (sum(g.amount) *
3367                DECODE(g.account_class, 'REV', 1,
3368                   DECODE(g.rec_offset_flag, 'Y', 1, -1))))
3369                      * DECODE(g.account_class, 'REV', 1,
3370                           DECODE(g.rec_offset_flag, 'Y', 1, -1))  ROUND_AMT,
3371          /* PERCENT LOGIC */
3372          (DECODE(g.rec_offset_flag, 'Y', 100,
3373              DECODE(r.deferred_revenue_flag, 'Y',
3374                 DECODE(t.invoicing_rule_id, -2, 0, 100),
3375                 100))
3376           - (sum(g.percent) *
3377                DECODE(g.account_class, 'REV', 1,
3378                  DECODE(g.rec_offset_flag, 'Y', 1, -1))))
3379                   * DECODE(g.account_class, 'REV', 1,
3380                       DECODE(g.rec_offset_flag, 'Y', 1, -1))  ROUND_PCT,
3381          /* ACCTD_AMOUNT LOGIC */
3382          (DECODE(p_base_mau, NULL,
3383             ROUND(DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3384                      DECODE(r.deferred_revenue_flag, 'Y',
3385                         DECODE(t.invoicing_rule_id, -2, 0, l.revenue_amount),
3386                              l.revenue_amount))
3387                    * nvl(t.exchange_rate,1), p_base_precision),
3388             ROUND((DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3389                       DECODE(r.deferred_revenue_flag, 'Y',
3390                         DECODE(t.invoicing_rule_id, -2, 0, l.revenue_amount),
3391                              l.revenue_amount))
3392                    * nvl(t.exchange_rate,1)) / p_base_mau) * p_base_mau)
3393           - (sum(g.acctd_amount) *
3394                DECODE(g.account_class, 'REV', 1,
3395                  DECODE(g.rec_offset_flag, 'Y', 1, -1))))
3396                   * DECODE(g.account_class, 'REV', 1,
3397                       DECODE(g.rec_offset_flag, 'Y', 1, -1))  ROUND_ACCT_AMT,
3398          /* END ACCTD_AMOUNT LOGIC */
3399          g.rec_offset_flag
3400   from   ra_customer_trx_lines l,
3401          ra_cust_trx_line_gl_dist g,
3402          ra_customer_trx t,
3403          ra_rules r
3404   where  t.customer_trx_id = p_trx_id
3405   and    l.customer_trx_id = t.customer_trx_id
3406   and    l.customer_trx_id = g.customer_trx_id
3407   and    l.customer_trx_line_id = g.customer_trx_line_id
3408          /* Skip any entries created by revenue adjustments
3409             or for deferred rules */
3410   and    l.accounting_rule_id = r.rule_id
3411   and    g.revenue_adjustment_id is NULL
3412          /* Only round transaction lines with rules */
3413   and    l.accounting_rule_id is not NULL
3414   and    l.autorule_complete_flag is NULL
3415   and    g.account_class IN ('REV','UNEARN','UNBILL')
3416   and    g.account_set_flag = 'N'
3417          /* Only round lines that actually have a rec_offset row */
3418   and exists ( SELECT 'has rof row'
3419                FROM   ra_cust_trx_line_gl_dist rof
3420                WHERE  rof.customer_trx_line_id = g.customer_trx_line_id
3421                AND    rof.account_set_flag = 'N'
3422                AND    rof.account_class in ('UNEARN','UNBILL')
3423                AND    rof.rec_offset_flag = 'Y')
3424   having
3425          /* AMOUNT LOGIC */
3426          (sum(g.amount) <>  DECODE(g.account_class, 'REV', l.revenue_amount,
3427                               DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3428                                              l.revenue_amount * -1)) *
3429                   DECODE(r.deferred_revenue_flag, 'Y',
3430                     DECODE(g.rec_offset_flag, 'Y', 1,
3431                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) or
3432          /* PERCENT LOGIC */
3433          sum(g.percent) <> DECODE(g.account_class, 'REV', 100,
3434                             DECODE(g.rec_offset_flag, 'Y', 100, -100)) *
3435                   DECODE(r.deferred_revenue_flag, 'Y',
3436                     DECODE(g.rec_offset_flag, 'Y', 1,
3437                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) or
3438          /* ACCTD_AMOUNT LOGIC */
3439          sum(g.acctd_amount) <> DECODE(p_base_mau, NULL,
3440                     ROUND(l.revenue_amount * nvl(t.exchange_rate,1), p_base_precision),
3441                     ROUND((l.revenue_amount * nvl(t.exchange_rate,1)) /
3442                                             p_base_mau) * p_base_mau) *
3443                   DECODE(r.deferred_revenue_flag, 'Y',
3444                     DECODE(g.rec_offset_flag, 'Y', 1,
3445                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) *
3446                   DECODE(g.account_class, 'REV', 1,
3447                     DECODE(g.rec_offset_flag, 'Y', 1, -1)))
3448          /* Only round lines w/unposted distributions */
3449   and    min(g.posting_control_id) = -3
3450 group by l.customer_trx_line_id, g.account_class, g.rec_offset_flag,
3451          l.revenue_amount, t.exchange_rate, r.deferred_revenue_flag,
3452          t.invoicing_rule_id;
3453 
3454 BEGIN
3455 
3456   IF PG_DEBUG in ('Y', 'C') THEN
3457      arp_standard.debug( 'arp_rounding.correct_rule_records_by_line()+ ' ||
3458                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3459   END IF;
3460 
3461   IF (P_CUSTOMER_TRX_ID IS NOT NULL) THEN
3462     /* Form and Rev Rec variant */
3463 
3464     IF (P_FIX_REC_OFFSET = 'Y') THEN
3465        /* Verify that rec_offset_flag(s) are set for this transaction
3466           and set them if they are not */
3467        set_rec_offset_flag(p_customer_trx_id, null, l_result);
3468 
3469        IF PG_DEBUG in ('Y', 'C') THEN
3470            arp_standard.debug('  result from set_rec_offset_flag() call : ' || l_result);
3471        END IF;
3472 
3473     END IF;
3474 
3475      /* This is phase 1 of rounding.
3476         Here, we make sure that debits equal credits (REV and UNEARN dists)
3477         on a gl_date basis.  We do this for both RAM and conventional
3478         distributions.  If there is a problem, we correct it
3479         on that date. */
3480      true_lines_by_gl_date(p_customer_trx_id);
3481 
3482      /* This is phase 2 of rounding.
3483         With this cursor and subsequent UPDATE, we detect situations
3484         where REV, UNEARN, or UNEARN(rof) for each line do not total
3485         to the revenue_amount of the line.  This routine assumes that
3486         the previous one has executed and that everything is already
3487         in balance by gl_date.
3488 
3489         NOTE:  Under normal circumstances, this routine will only make
3490         changes to distributions as part of Revenue Recognition.  It
3491         should not make changes based on form-level adjustments or
3492         RAM adjustments (after Revenue Recognition has completed).
3493 
3494         As of bug 3033850, I revised the rounding logic to execute up
3495         to three separate times/phases to handle unusual cases (opposite sign,
3496         zero dists)  The code will execute first for same sign rounding,
3497         then opposite sign, and finally, using zero sign dists.  The code
3498         should be able to detect if rounding is complete and exit after
3499         having rounded all the distributions.  Even if only 1 or two phases
3500         have been completed.
3501 
3502         The phases/passes are:
3503           1=Dists with any sign (same, opposite, or zero) as line (UPDATE)
3504           2=Dists where corrections cause signs to mismatch (+/-) (INSERT)
3505           3=Continuation of 4, corrections themselves have opposite signs (INSERT)
3506 
3507         Note:  phase 2 and 3 will only function if the acctd_amount
3508              correction is a different sign than the entered amount.
3509 
3510         */
3511 
3512      OPEN round_rows_by_trx(P_CUSTOMER_TRX_ID, P_BASE_MAU, P_BASE_PRECISION);
3513 	FETCH round_rows_by_trx BULK COLLECT INTO
3514                              t_line_id,
3515                              t_account_class,
3516                              t_round_amount,
3517                              t_round_percent,
3518                              t_round_acctd,
3519                              t_rec_offset;
3520 
3521         l_rows_needing_rounding := round_rows_by_trx%ROWCOUNT;
3522 
3523         CLOSE round_rows_by_trx;
3524 
3525   ELSE
3526      /* Autoinvoice variant */
3527      /* No reason to round line-based distributions */
3528      l_rows_needing_rounding := 0;
3529      RETURN (iTRUE);
3530 
3531   END IF;
3532 
3533   /* Now update all the rows that require it */
3534 
3535   IF PG_DEBUG in ('Y', 'C') THEN
3536      arp_standard.debug('Rows that need rounding: ' || l_rows_needing_rounding);
3537   END IF;
3538 
3539   IF (l_rows_needing_rounding > 0) THEN
3540 
3541      /* DEBUG CODE +/
3542                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
3543                    arp_standard.debug(err || ' ' || t_line_id(err)|| '  ' ||
3544                                       t_account_class(err) ||
3545                      '  ' || t_rec_offset(err) ||
3546                      '  ' || t_round_amount(err) ||
3547                      ' ' || t_round_acctd(err) || ' ' ||
3548                      t_round_percent(err) );
3549                 END LOOP;
3550      /+ END DEBUG CODE */
3551 
3552      /* START - Main Loop */
3553      WHILE (l_phase < 3 and l_rows_needing_rounding - l_rows_rounded > 0)
3554      LOOP
3555 
3556         l_phase := l_phase + 1;
3557 
3558         IF PG_DEBUG in ('Y', 'C') THEN
3559             arp_standard.debug('  Pass = ' || l_phase);
3560         END IF;
3561 
3562         IF l_phase = 1
3563         THEN
3564 
3565           /* 9160123 - changed rounding code from 5 phases to 3 and
3566              simplified the update logic.  The original phases 1-3
3567              are now handled in a single call (phase 1).  The original
3568              phases 4 and 5 are now 2 and 3 respectively.  The need
3569              for phases 1-3 was replaced in the simplified logic by
3570              DECODES that map a '3', '2', or '1' as 9th digit in the sorted
3571              string that uses gl_date, amount, and gl_dist_id.  This logic
3572              was forward ported from version 115.59.15101.3.  */
3573 
3574           /* In the logic below, we fetch the gl_date, a single
3575              digit (3, 2, or 1) representing signs, the amount, and
3576              the gl_dist_id and append them in that order.. the result
3577              looks like this:
3578 
3579              200908123000000000000123.710000000000123412341234
3580              GL_DATE|#|GL_DIST_AMOUNT__|GL_DIST_ID___________|
3581 
3582              In this example, the gl_date of this gl_dist row
3583              is 12-AUG-2009. The '3' indicates that the gl_dist
3584              amount and line.revenue_amount are of same sign.
3585              The gl_dist.amount is 123.71 and the gl_dist_id is
3586              123412341234.  The sql would return only the gl_dist_id
3587              of the distribution for each account class to be
3588              rounded.
3589 
3590              The sql selects one REV, one UNEARN(rof), and
3591              one UNEARN(non-rof) for each trx_line_id.  */
3592 
3593 
3594           FORALL i IN t_line_id.FIRST .. t_line_id.LAST
3595            UPDATE ra_cust_trx_line_gl_dist
3596            SET    amount = amount + t_round_amount(i),
3597                   percent = percent + t_round_percent(i),
3598                   acctd_amount = acctd_amount + t_round_acctd(i),
3599                   last_updated_by = arp_global.last_updated_by,
3600                   last_update_date = sysdate
3601            WHERE  cust_trx_line_gl_dist_id in (
3602               /* Bug 4082528 - Select restructured */
3603               /* START OF GL_DIST_ID SELECT */
3604               select
3605                 to_number(substr(max(
3606                        to_char(g.gl_date,'YYYYMMDD') ||
3607                        decode(sign(g.amount *
3608                                  DECODE(g.account_class, 'REV', 1,
3609                                    DECODE(g.rec_offset_flag, 'Y', 1, -1))),
3610                               sign(tl.revenue_amount), '3',
3611                            sign(tl.revenue_amount * -1), '2', '1') ||
3612                        ltrim(to_char(abs(g.amount),'099999999999999.00')) ||
3613                        ltrim(to_char(g.cust_trx_line_gl_dist_id,
3614                                           '0999999999999999999999'))),28))
3615               from   ra_cust_trx_line_gl_dist g,
3616                      ra_customer_trx_lines tl
3617               where  g.customer_trx_line_id = t_line_id(i)
3618               and    tl.customer_trx_line_id = g.customer_trx_line_id
3619               and    g.account_class = t_account_class(i)
3620               and    g.account_set_flag = 'N'
3621                      /* ONLY USE UNPOSTED ROWS */
3622               and    g.posting_control_id = -3
3623                      /* ONLY CONSIDERS REC_OFFSET_FLAG IF NOT NULL */
3624               and    nvl(g.rec_offset_flag, '~') = nvl(t_rec_offset(i), '~')
3625                      /* DO NOT ROUND RAM DISTRIBUTIONS */
3626               and    g.revenue_adjustment_id is null
3627                      /* SKIP UPDATE IF SIGNS ARE OPPOSITE */
3628               and   (sign(g.amount + t_round_amount(i)) =
3629                      sign(g.acctd_amount + t_round_acctd(i)) or
3630                      sign(g.amount + t_round_amount(i)) = 0)
3631               /* END OF GL_DIST_ID SELECT */
3632               );
3633         ELSE
3634            /* 6325023 - added 2nd phase to handle SLA issues where
3635               entered and acctd_amount dists have opposite signs */
3636            /* 6473284 - Added 3rd phase to extend fix for 6325023 to
3637                cover some odd corner cases. */
3638 
3639 
3640            FORALL i in t_line_id.first .. t_line_id.last
3641             INSERT INTO RA_CUST_TRX_LINE_GL_DIST
3642               (CUST_TRX_LINE_GL_DIST_ID,
3643                CREATED_BY,
3644                CREATION_DATE,
3645                LAST_UPDATED_BY,
3646                LAST_UPDATE_DATE,
3647                LAST_UPDATE_LOGIN,
3648                PROGRAM_APPLICATION_ID,
3649                PROGRAM_ID,
3650                PROGRAM_UPDATE_DATE,
3651                POSTING_CONTROL_ID,
3652                SET_OF_BOOKS_ID,
3653                CUSTOMER_TRX_LINE_ID,
3654                CUSTOMER_TRX_ID,
3655                ACCOUNT_CLASS,
3656                CODE_COMBINATION_ID,
3657                AMOUNT,
3658                ACCTD_AMOUNT,
3659                PERCENT,
3660                GL_DATE,
3661                ORIGINAL_GL_DATE,
3662                ACCOUNT_SET_FLAG,
3663                COMMENTS,
3664                ATTRIBUTE_CATEGORY,
3665                ATTRIBUTE1,
3666                ATTRIBUTE2,
3667                ATTRIBUTE3,
3668                ATTRIBUTE4,
3669                ATTRIBUTE5,
3670                ATTRIBUTE6,
3671                ATTRIBUTE7,
3672                ATTRIBUTE8,
3673                ATTRIBUTE9,
3674                ATTRIBUTE10,
3675                ATTRIBUTE11,
3676                ATTRIBUTE12,
3677                ATTRIBUTE13,
3678                ATTRIBUTE14,
3679                ATTRIBUTE15,
3680                LATEST_REC_FLAG,
3681                USSGL_TRANSACTION_CODE,
3682                REC_OFFSET_FLAG,
3683                USER_GENERATED_FLAG,
3684                ORG_ID,
3685                REQUEST_ID,
3686                CUST_TRX_LINE_SALESREP_ID,
3687                ROUNDING_CORRECTION_FLAG
3688               )
3689         SELECT
3690             RA_CUST_TRX_LINE_GL_DIST_S.NEXTVAL,
3691             CREATED_BY,
3692             CREATION_DATE,
3693             LAST_UPDATED_BY,
3694             LAST_UPDATE_DATE,
3695             LAST_UPDATE_LOGIN,
3696             PROGRAM_APPLICATION_ID,
3697             PROGRAM_ID,
3698             PROGRAM_UPDATE_DATE,
3699             -3,
3700             SET_OF_BOOKS_ID,
3701             CUSTOMER_TRX_LINE_ID,
3702             CUSTOMER_TRX_ID,
3703             ACCOUNT_CLASS,
3704             CODE_COMBINATION_ID,
3705             DECODE(l_phase, 2, t_round_amount(i), 0),
3706             DECODE(l_phase, 2,
3707               DECODE(SIGN(t_round_amount(i)),0,t_round_acctd(i),
3708                    ABS(t_round_acctd(i)) * SIGN(t_round_amount(i))),
3709               t_round_acctd(i) * 2),
3710             DECODE(l_phase, 2, t_round_percent(i), 0),
3711             GL_DATE,
3712             ORIGINAL_GL_DATE,
3713             ACCOUNT_SET_FLAG,
3714             'PHASE ' || l_phase || ':  Rounding correction derived from ' ||
3715                cust_trx_line_gl_dist_id,
3716             ATTRIBUTE_CATEGORY,
3717             ATTRIBUTE1,
3718             ATTRIBUTE2,
3719             ATTRIBUTE3,
3720             ATTRIBUTE4,
3721             ATTRIBUTE5,
3722             ATTRIBUTE6,
3723             ATTRIBUTE7,
3724             ATTRIBUTE8,
3725             ATTRIBUTE9,
3726             ATTRIBUTE10,
3727             ATTRIBUTE11,
3728             ATTRIBUTE12,
3729             ATTRIBUTE13,
3730             ATTRIBUTE14,
3731             ATTRIBUTE15,
3732             LATEST_REC_FLAG,
3733             USSGL_TRANSACTION_CODE,
3734             REC_OFFSET_FLAG,
3735             USER_GENERATED_FLAG,
3736             ORG_ID,
3737             REQUEST_ID,
3738             CUST_TRX_LINE_SALESREP_ID,
3739             'Y'
3740         FROM  RA_CUST_TRX_LINE_GL_DIST_ALL
3741         WHERE CUST_TRX_LINE_GL_DIST_ID IN (
3742               /* SELECT GL_DIST_ID FOR EACH LINE THAT
3743                  REQUIRES ROUNDING */
3744               select
3745                 to_number(substr(max(
3746                        to_char(g.gl_date,'YYYYMMDD') ||
3747                        decode(sign(g.amount *
3748                                  DECODE(g.account_class, 'REV', 1,
3749                                    DECODE(g.rec_offset_flag, 'Y', 1, -1))),
3750                               sign(tl.revenue_amount), '3',
3751                            sign(tl.revenue_amount * -1), '2', '1') ||
3752                        ltrim(to_char(abs(g.amount),'099999999999999.00')) ||
3753                        ltrim(to_char(g.cust_trx_line_gl_dist_id,
3754                                           '0999999999999999999999'))),28))
3755               from   ra_cust_trx_line_gl_dist g,
3756                      ra_customer_trx_lines tl
3757               where  g.customer_trx_line_id = t_line_id(i)
3758               and    tl.customer_trx_line_id = g.customer_trx_line_id
3759               and    g.account_class = t_account_class(i)
3760               and    g.account_set_flag = 'N'
3761                      /* ONLY USE UNPOSTED ROWS */
3762               and    g.posting_control_id = -3
3763                      /* ONLY CONSIDERS REC_OFFSET_FLAG IF NOT NULL */
3764               and    nvl(g.rec_offset_flag, '~') = nvl(t_rec_offset(i), '~')
3765                      /* DO NOT ROUND RAM DISTRIBUTIONS */
3766               and    g.revenue_adjustment_id is null
3767               /* END OF GL_DIST_ID SELECT */
3768               );
3769 
3770         END IF;
3771 
3772        l_rows_rounded_this_pass := 0;
3773 
3774        /* START - Cleanup loop */
3775        FOR upd in t_line_id.FIRST .. t_line_id.LAST LOOP
3776 
3777           IF(SQL%BULK_ROWCOUNT(upd) = 1)
3778           THEN
3779 
3780           /* This piece of code determines that 1 row was updated
3781              for each invoice line and account class.  Once the
3782              row is updated, we need to remove it from further
3783              consideration.  To do that, we change the line_id
3784              to line_id * -1 (a row that should never exist)
3785              and this prevents it from being processed in
3786              subsequent passes.
3787 
3788              Incidentally, I tried to just delete the
3789              processed rows - but this caused subsequent
3790              passes to fail with ORA errors due to missing
3791              plsql table rows.  The bulk update requires
3792              a continuous list in sequential order and, by deleting
3793              rows from the table, we cause the update to fail.
3794           */
3795 
3796               IF PG_DEBUG in ('Y', 'C') THEN
3797                  arp_standard.debug('  Target: ' || t_line_id(upd) ||
3798                                 '  ' || t_account_class(upd) ||
3799                                 '  ' || t_rec_offset(upd) ||
3800                                 '  ' || t_round_amount(upd) ||
3801                                 '  ' || t_round_acctd(upd) ||
3802                                 ' ' || t_round_percent(upd) ||
3803                                 ' ' || SQL%BULK_ROWCOUNT(upd));
3804               END IF;
3805 
3806 
3807               IF l_phase = 2
3808               THEN
3809                  /* extra checks to see if we need last phase */
3810                  IF t_round_amount(upd) = 0
3811                     OR  t_round_acctd(upd) = 0
3812                     OR  SIGN(t_round_amount(upd)) = SIGN(t_round_acctd(upd))
3813                  THEN
3814                     /* This phase inserted complete dists
3815                        so no need to insert another dist */
3816                     l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
3817                     t_line_id(upd) := -1 * t_line_id(upd);
3818                  ELSE
3819                     /* Do not change the line_id or increment.. this
3820                         forces the last phase and an insert of
3821                         a dist with amount=0 and acctd_amount=<correction * 2>
3822                     */
3823                     NULL;
3824                  END IF;
3825               ELSE
3826                  /* previous behavior */
3827                  l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
3828                  /* make line_id negative so it causes no further updates */
3829                  t_line_id(upd) := -1 * t_line_id(upd);
3830               END IF;
3831           END IF;
3832 
3833           IF(SQL%BULK_ROWCOUNT(upd) > 1)
3834           THEN
3835              /* Failure condition 1
3836                 This section of code executes only when more than
3837                 one line is updated for a given customer_trx_line_id
3838                 and account_class.  That would mean that the rounding
3839                 logic was unable to identify a single line for update
3840                 and rounding would then raise an error to roll back
3841                 any corrections or calculations for this transaction.
3842 
3843                 Revenue recognition has been modified to roll back
3844                 transactions that fail and to document the lines
3845                 that have problems.  */
3846 
3847              IF PG_DEBUG in ('Y', 'C')
3848              THEN
3849 
3850                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
3851                    arp_standard.debug(t_line_id(err)|| '  ' ||
3852                                       t_account_class(err) ||
3853                      '  ' || t_rec_offset(err) ||
3854                      '  ' || t_round_amount(err) ||
3855                      ' ' || t_round_acctd(err) || ' ' ||
3856                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
3857                 END LOOP;
3858 
3859              END IF;
3860 
3861              p_error_message := 'arp.rounding:  Error identifying rows for correction.  trx_id = ' || p_customer_trx_id;
3862 
3863              RETURN(iFALSE);
3864 
3865           END IF;
3866 
3867        END LOOP; /* END - Cleanup loop */
3868 
3869        IF PG_DEBUG in ('Y', 'C') THEN
3870           arp_standard.debug('    Rows rounded this pass : ' || l_rows_rounded_this_pass);
3871        END IF;
3872 
3873        l_rows_rounded := l_rows_rounded + l_rows_rounded_this_pass;
3874 
3875      END LOOP;  /* END - Main processing loop */
3876 
3877        IF (l_rows_needing_rounding <> l_rows_rounded) THEN
3878 
3879           /* Failure condition 2
3880              In this situation, the total number of distributions corrected
3881              does not match the number expected.  Because of condition 1
3882              handled above, this would only occur if we were unable to
3883              locate any rows to assess rounding corrections to for
3884              one or more invoice lines.  Such situations highlight
3885              shortcomings in this logic that must be investigated
3886              and corrected.
3887           */
3888 
3889           IF PG_DEBUG in ('Y', 'C') THEN
3890              arp_standard.debug('Mismatch between lines found and lines updated (see below)');
3891              arp_standard.debug('  Rows targeted: ' || l_rows_needing_rounding);
3892              arp_standard.debug('  Rows rounded : ' || l_rows_rounded);
3893 
3894              FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
3895 
3896                  arp_standard.debug(t_line_id(err) || '  ' || t_account_class(err) ||
3897                      '  ' || t_rec_offset(err) ||
3898                      '  ' || t_round_amount(err) || ' ' || t_round_acctd(err) || ' ' ||
3899                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
3900 
3901              END LOOP;
3902 
3903           END IF;
3904 
3905             p_error_message := ' arp_rounding: Error identifying rows for correction. ' ||
3906                                ' trx_id = ' || p_customer_trx_id;
3907 
3908           RETURN(iFALSE);
3909        END IF;
3910 
3911        p_rows_processed := p_rows_processed + l_rows_rounded;
3912        IF PG_DEBUG in ('Y', 'C') THEN
3913           arp_standard.debug('Total number of rows updated:  ' || l_rows_rounded);
3914        END IF;
3915 
3916   /* MRC Processing */
3917   IF PG_DEBUG in ('Y', 'C') THEN
3918      arp_standard.debug('doing rounding for MRC if necessary');
3919   END IF;
3920   ar_mrc_engine2.mrc_correct_rounding(
3921                    'CORRECT_RULE_RECORDS_BY_LINE',
3922                    P_REQUEST_ID,
3923                    P_CUSTOMER_TRX_ID,
3924                    NULL,    /* customer trx line id */
3925                    P_TRX_CLASS_TO_PROCESS,
3926          	   NULL,   /* concat_segs */
3927                    NULL,  /* balanced round_ccid */
3928                    p_check_rules_flag,
3929                    p_period_set_name
3930                   );
3931 
3932   END IF;
3933 
3934   IF PG_DEBUG in ('Y', 'C') THEN
3935      arp_standard.debug('arp_rounding.correct_rule_records_by_line()- ' ||
3936                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3937   END IF;
3938 
3939   RETURN(iTRUE);
3940 END correct_rule_records_by_line;
3941 
3942 /*-------------------------------------------------------------------------+
3943  | PRIVATE FUNCTION                                                        |
3944  |   correct_rev_adj_by_line()                                        |
3945  |                                                                         |
3946  | DESCRIPTION                                                             |
3947  |   This function corrects rounding errors resulting from revenue
3948  |   adjustments created via ar_revenue_adjustment_pvt.dists_by_model
3949  |   routine.  The logic contained below is almost identical to
3950  |   correct_rule_records_by_line (although it has been altered to
3951  |   drive from AR_LINE_REV_ADJ_GT table (capable of rounding
3952  |   multiple transactions or adjustments at one time).
3953  |
3954  |   See description of correct_rule_records_by_line for details about
3955  |   the architecture of this function.
3956  |
3957  |   NOTE:  Due to the unique data available for RAM adjustments, it was
3958  |   not possible to round percents consistently at this time.  amount and
3959  |   acctd_amount columns will be rounded -- but percents will not.
3960  +-------------------------------------------------------------------------*/
3961 
3962 FUNCTION correct_rev_adj_by_line
3963         RETURN NUMBER IS
3964 
3965   t_line_id       l_line_id_type;
3966   t_gl_id         l_line_id_type;
3967   t_round_amount  l_amount_type;
3968   t_round_percent l_percent_type;
3969   t_round_acctd   l_amount_type;
3970   t_account_class l_acct_class;
3971   t_rev_adj_id    l_line_id_type;
3972 
3973   l_rows_needing_rounding NUMBER;
3974   l_rows_rounded NUMBER := 0;
3975   l_rows_rounded_this_pass NUMBER := 0;
3976   l_phase NUMBER := 0;
3977 
3978   /* Cursor for FINAL rounding
3979      Detects which customer_trx_line_ids require rounding
3980      and determines the amount, acctd_amount, and percent
3981      for each account_class */
3982 
3983   CURSOR round_rows_by_trx(p_base_mau NUMBER,
3984                            p_base_precision NUMBER) IS
3985   select /*+ leading(gt t) index(l ra_customer_trx_lines_u1) index(g ra_cust_trx_line_gl_dist_n1)*/
3986          l.customer_trx_line_id, g.account_class,
3987          /* AMOUNT LOGIC */
3988          (gt.amount
3989           - (sum(g.amount)
3990               * DECODE(g.account_class, 'REV',1,-1)))
3991                  * DECODE(g.account_class, 'REV',1,-1)        ROUND_AMT,
3992          /* END AMOUNT LOGIC */
3993          /* Leaving percent alone for now */
3994          0                                                    ROUND_PCT,
3995          /* ACCTD_AMOUNT LOGIC */
3996          (DECODE(p_base_mau, NULL,
3997             ROUND(gt.amount
3998                * nvl(t.exchange_rate,1), p_base_precision),
3999             ROUND((gt.amount
4000                * nvl(t.exchange_rate,1))
4001                     / p_base_mau) * p_base_mau)
4002           - (sum(g.acctd_amount)
4003                * DECODE(g.account_class, 'REV', 1, -1)))
4004                   * DECODE(g.account_class, 'REV', 1, -1)     ROUND_ACCT_AMT,
4005          /* END ACCTD_AMOUNT LOGIC */
4006          gt.revenue_adjustment_id
4007   from   ra_customer_trx_lines    l,
4008          ar_line_rev_adj_gt       gt,
4009          ra_cust_trx_line_gl_dist g,
4010          ra_customer_trx          t
4011   where  t.customer_trx_id = gt.customer_trx_id
4012   and    l.customer_trx_id = t.customer_trx_id
4013   and    l.customer_trx_id = g.customer_trx_id
4014   and    l.customer_trx_line_id = g.customer_trx_line_id
4015 /* Bug Number 6782307 -- Added the below join condition */
4016   and    l.customer_trx_line_id = gt.customer_trx_line_id
4017   and    g.revenue_adjustment_id = gt.revenue_adjustment_id
4018   and    l.autorule_complete_flag is NULL
4019   and    g.account_class IN ('REV','UNEARN','UNBILL')
4020   and    g.account_set_flag = 'N'
4021   having
4022          /* AMOUNT LOGIC */
4023          (sum(g.amount) <>  gt.amount *
4024                    DECODE(g.account_class, 'REV',1,-1) or
4025          /* PERCENT LOGIC
4026          sum(g.percent) <> DECODE(g.account_class, 'REV', 100,
4027                             DECODE(g.rec_offset_flag, 'Y', 100, -100)) *
4028                   DECODE(r.deferred_revenue_flag, 'Y',
4029                     DECODE(g.rec_offset_flag, 'Y', 1,
4030                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) or */
4031          /* ACCTD_AMOUNT LOGIC */
4032          sum(g.acctd_amount) <> DECODE(p_base_mau, NULL,
4033                     ROUND(gt.amount
4034                        * nvl(t.exchange_rate,1), p_base_precision),
4035                     ROUND((gt.amount
4036                        * nvl(t.exchange_rate,1)) /
4037                                p_base_mau) * p_base_mau) *
4038                   DECODE(g.account_class, 'REV', 1,-1))
4039          /* Only round lines w/unposted distributions */
4040   and    min(g.posting_control_id) = -3
4041 group by l.customer_trx_line_id, g.account_class,
4042          gt.revenue_adjustment_id, gt.amount, t.exchange_rate;
4043 
4044 BEGIN
4045 
4046   IF PG_DEBUG in ('Y', 'C') THEN
4047      arp_standard.debug('arp_rounding.correct_rev_adj_by_line()+ ');
4048   END IF;
4049 
4050      /* This is phase 1 of rounding.
4051         Here, we make sure that debits equal credits (REV and UNEARN dists)
4052         on a gl_date basis.  We do this for both RAM and conventional
4053         distributions.  If there is a problem, we correct it
4054         on that date. */
4055 
4056      /* Passing null to this routine forces it to drive using a join
4057         to ar_line_rev_adj_gt table */
4058      true_lines_by_gl_date(null);
4059 
4060      /* This is phase 2 of rounding.
4061         With this cursor and subsequent UPDATE, we detect situations
4062         where REV or UNEARN for each line do not total
4063         to the adjustment amount of the line.  This routine assumes that
4064         the previous one has executed and that everything is already
4065         in balance by gl_date.
4066 
4067         The phases are 1=Dists with same sign as line
4068                        2=Dists with opposite sign as line
4069                        3=Dists with zero amount (when line is non-zero
4070                        4=Dists where acctd_amount sign changes */
4071 
4072      OPEN round_rows_by_trx(AR_RAAPI_UTIL.g_min_acc_unit,
4073                             AR_RAAPI_UTIL.g_trx_precision);
4074 	FETCH round_rows_by_trx BULK COLLECT INTO
4075                              t_line_id,
4076                              t_account_class,
4077                              t_round_amount,
4078                              t_round_percent,
4079                              t_round_acctd,
4080                              t_rev_adj_id;
4081 
4082         l_rows_needing_rounding := round_rows_by_trx%ROWCOUNT;
4083 
4084         CLOSE round_rows_by_trx;
4085 
4086   /* Now update all the rows that require it */
4087 
4088   IF PG_DEBUG in ('Y', 'C') THEN
4089      arp_standard.debug('Rows that need rounding: ' || l_rows_needing_rounding);
4090   END IF;
4091 
4092   IF (l_rows_needing_rounding > 0) THEN
4093 
4094      /* DEBUG CODE +/
4095                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
4096                    arp_standard.debug(err || ' ' || t_line_id(err)|| '  ' ||
4097                                       t_account_class(err) ||
4098                      '  ' || t_round_amount(err) ||
4099                      ' ' || t_round_acctd(err) || ' ' ||
4100                      t_round_percent(err) );
4101                 END LOOP;
4102      /+ END DEBUG CODE */
4103 
4104      /* START - Main Loop */
4105      WHILE (l_phase < 5 and l_rows_needing_rounding - l_rows_rounded > 0)
4106      LOOP
4107 
4108         l_phase := l_phase + 1;
4109 
4110         IF PG_DEBUG in ('Y', 'C') THEN
4111             arp_standard.debug('  Pass = ' || l_phase);
4112         END IF;
4113 
4114         IF l_phase <=3
4115         THEN
4116           FORALL i IN t_line_id.FIRST .. t_line_id.LAST
4117            UPDATE ra_cust_trx_line_gl_dist
4118            SET    amount = amount + t_round_amount(i),
4119                   percent = percent + t_round_percent(i),
4120                   acctd_amount = acctd_amount + t_round_acctd(i),
4121                   last_updated_by = arp_global.last_updated_by,
4122                   last_update_date = sysdate
4123            WHERE  cust_trx_line_gl_dist_id in (
4124               /* SELECT GL_DIST_ID FOR EACH LINE THAT
4125                  REQUIRES ROUNDING */
4126               select MAX(g.cust_trx_line_gl_dist_id)
4127               from   ra_cust_trx_line_gl_dist g,
4128                      ra_cust_trx_line_gl_dist gmax,
4129                      ra_customer_trx_lines tl
4130               where  g.customer_trx_line_id = t_line_id(i)
4131               and    tl.customer_trx_line_id = g.customer_trx_line_id
4132               and    g.account_class = t_account_class(i)
4133               and    g.account_set_flag = 'N'
4134                      /* ONLY USE UNPOSTED ROWS */
4135               and    g.posting_control_id = -3
4136                      /* ONLY CONSIDERS NON-REC_OFFSET ROWS */
4137               and    g.rec_offset_flag IS NULL
4138                      /* only a specific rev_adj */
4139               and    g.revenue_adjustment_id = t_rev_adj_id(i)
4140                      /* FORCES USE OF ROW IN LAST PERIOD */
4141               and    g.gl_date = (
4142                          select max(gl_date)
4143                          from ra_cust_trx_line_gl_dist gdmax
4144                          where gdmax.customer_trx_line_id = g.customer_trx_line_id
4145                          and   gdmax.account_class = g.account_class
4146                          and   nvl(gdmax.rec_offset_flag, '~') =
4147                                          nvl(g.rec_offset_flag, '~')
4148                          and   gdmax.account_set_flag = 'N'
4149                          and   gdmax.posting_control_id = -3
4150                          and   gdmax.revenue_adjustment_id = t_rev_adj_id(i))
4151               and    gmax.customer_trx_line_id = g.customer_trx_line_id
4152               and    gmax.account_class = g.account_class
4153               and    gmax.account_set_flag = 'N'
4154               and    nvl(gmax.rec_offset_flag, '~') = nvl(g.rec_offset_flag, '~')
4155               and    gmax.gl_date = g.gl_date
4156                      /* ONLY RAM DISTRIBUTIONS */
4157               and    g.revenue_adjustment_id = gmax.revenue_adjustment_id
4158                      /* USE DISTS THAT MATCH SIGN OF LINE FIRST,
4159                         THEN OTHERS (ZERO, NEGATIVE). */
4160               and    (SIGN(g.amount) = SIGN(tl.revenue_amount) *
4161                                    DECODE(g.account_class, 'REV', 1,
4162                                       DECODE(g.rec_offset_flag, 'Y', 1, -1)) *
4163                                    DECODE(l_phase, 1, 1, 2, -1, 0))
4164                       /* SKIP UPDATE IF SIGNS AR OPPOSITE */
4165               and   (sign(g.amount + t_round_amount(i)) =
4166                      sign(g.acctd_amount + t_round_acctd(i)) or
4167                      sign(g.amount + t_round_amount(i)) = 0)
4168               having
4169                      /* USE LINE WITH LARGEST ABS(AMOUNT) */
4170                      g.amount = decode(sign(g.amount), -1, MIN(gmax.amount),
4171                                                         1, MAX(gmax.amount),
4172                                                         0)
4173               group by g.amount
4174               /* END OF GL_DIST_ID SELECT */
4175               );
4176         ELSE
4177            /* 6325023 - added 4th phase to handle SLA issues where
4178               entered and acctd_amount dists have opposite signs */
4179            /* 6473284 - Added 5th phase to extend fix for 6325023 to
4180                cover some odd corner cases.
4181 
4182               In discussing these phases, we are now focused on
4183               the signs of the amount and acctd corrections only.  If
4184               Either is zero or they are same sign, then we update the
4185               existing dists (phase 1-3), however, if the corrections force
4186               the resulting amount or acctd to be a different sign, then
4187               phase 4 and 5 may each insert additional distributions.
4188 
4189               Phase 4 inserts a new distribution if the signs become
4190               opposites after rounding.  Phase 5 splits entered and
4191               acctd when the amounts themselves are opposite signs
4192 
4193               Based on bug 6473284, I'm going to coin a new phrase..
4194               cases where the rounding is pennies is now called
4195               near-zero rounding.  Phases 4 and 5 are specific to
4196               cases where the rounding amount is near-zero (pennies)
4197               and the effect of that rounding makes the distributions
4198               change signs unpredictably.   This is just FYI   */
4199 
4200            FORALL i in t_line_id.first .. t_line_id.last
4201             INSERT INTO RA_CUST_TRX_LINE_GL_DIST
4202               (CUST_TRX_LINE_GL_DIST_ID,
4203                CREATED_BY,
4204                CREATION_DATE,
4205                LAST_UPDATED_BY,
4206                LAST_UPDATE_DATE,
4207                LAST_UPDATE_LOGIN,
4208                PROGRAM_APPLICATION_ID,
4209                PROGRAM_ID,
4210                PROGRAM_UPDATE_DATE,
4211                POSTING_CONTROL_ID,
4212                SET_OF_BOOKS_ID,
4213                CUSTOMER_TRX_LINE_ID,
4214                CUSTOMER_TRX_ID,
4215                ACCOUNT_CLASS,
4216                CODE_COMBINATION_ID,
4217                AMOUNT,
4218                ACCTD_AMOUNT,
4219                PERCENT,
4220                GL_DATE,
4221                ORIGINAL_GL_DATE,
4222                ACCOUNT_SET_FLAG,
4223                COMMENTS,
4224                ATTRIBUTE_CATEGORY,
4225                ATTRIBUTE1,
4226                ATTRIBUTE2,
4227                ATTRIBUTE3,
4228                ATTRIBUTE4,
4229                ATTRIBUTE5,
4230                ATTRIBUTE6,
4231                ATTRIBUTE7,
4232                ATTRIBUTE8,
4233                ATTRIBUTE9,
4234                ATTRIBUTE10,
4235                ATTRIBUTE11,
4236                ATTRIBUTE12,
4237                ATTRIBUTE13,
4238                ATTRIBUTE14,
4239                ATTRIBUTE15,
4240                LATEST_REC_FLAG,
4241                USSGL_TRANSACTION_CODE,
4242                REC_OFFSET_FLAG,
4243                USER_GENERATED_FLAG,
4244                ORG_ID,
4245                REQUEST_ID,
4246                CUST_TRX_LINE_SALESREP_ID,
4247                REVENUE_ADJUSTMENT_ID,
4248                EVENT_ID,
4249                ROUNDING_CORRECTION_FLAG
4250               )
4251         SELECT
4252             RA_CUST_TRX_LINE_GL_DIST_S.NEXTVAL,
4253             CREATED_BY,
4254             CREATION_DATE,
4255             LAST_UPDATED_BY,
4256             LAST_UPDATE_DATE,
4257             LAST_UPDATE_LOGIN,
4258             PROGRAM_APPLICATION_ID,
4259             PROGRAM_ID,
4260             PROGRAM_UPDATE_DATE,
4261             -3,
4262             SET_OF_BOOKS_ID,
4263             CUSTOMER_TRX_LINE_ID,
4264             CUSTOMER_TRX_ID,
4265             ACCOUNT_CLASS,
4266             CODE_COMBINATION_ID,
4267             DECODE(l_phase, 4, t_round_amount(i), 0),
4268             DECODE(l_phase, 4,
4269               DECODE(SIGN(t_round_amount(i)),0,t_round_acctd(i),
4270                    ABS(t_round_acctd(i)) * SIGN(t_round_amount(i))),
4271               t_round_acctd(i) * 2),
4272             DECODE(l_phase, 4, t_round_percent(i), 0),
4273             GL_DATE,
4274             ORIGINAL_GL_DATE,
4275             ACCOUNT_SET_FLAG,
4276             'PHASE ' || l_phase || ':  Rounding correction derived from ' ||
4277                cust_trx_line_gl_dist_id,
4278             ATTRIBUTE_CATEGORY,
4279             ATTRIBUTE1,
4280             ATTRIBUTE2,
4281             ATTRIBUTE3,
4282             ATTRIBUTE4,
4283             ATTRIBUTE5,
4284             ATTRIBUTE6,
4285             ATTRIBUTE7,
4286             ATTRIBUTE8,
4287             ATTRIBUTE9,
4288             ATTRIBUTE10,
4289             ATTRIBUTE11,
4290             ATTRIBUTE12,
4291             ATTRIBUTE13,
4292             ATTRIBUTE14,
4293             ATTRIBUTE15,
4294             LATEST_REC_FLAG,
4295             USSGL_TRANSACTION_CODE,
4296             REC_OFFSET_FLAG,
4297             USER_GENERATED_FLAG,
4298             ORG_ID,
4299             REQUEST_ID,
4300             CUST_TRX_LINE_SALESREP_ID,
4301             REVENUE_ADJUSTMENT_ID,
4302             EVENT_ID,
4303             'Y'
4304         FROM  RA_CUST_TRX_LINE_GL_DIST_ALL
4305         WHERE CUST_TRX_LINE_GL_DIST_ID IN (
4306               /* SELECT GL_DIST_ID FOR EACH LINE THAT
4307                  REQUIRES ROUNDING */
4308               select
4309                 to_number(substr(max(
4310                        to_char(g.gl_date,'YYYYMMDD') ||
4311                        decode(sign(g.amount *
4312                                  DECODE(g.account_class, 'REV', 1,
4313                                    DECODE(g.rec_offset_flag, 'Y', 1, -1))),
4314                               sign(tl.revenue_amount), '3',
4315                            sign(tl.revenue_amount * -1), '2', '1') ||
4316                        ltrim(to_char(abs(g.amount),'099999999999999.00')) ||
4317                        ltrim(to_char(g.cust_trx_line_gl_dist_id,
4318                                           '0999999999999999999999'))),28))
4319               from   ra_cust_trx_line_gl_dist g,
4320                      ra_customer_trx_lines tl
4321               where  g.customer_trx_line_id = t_line_id(i)
4322               and    tl.customer_trx_line_id = g.customer_trx_line_id
4323               and    g.account_class = t_account_class(i)
4324               and    g.account_set_flag = 'N'
4325                      /* ONLY USE UNPOSTED ROWS */
4326               and    g.posting_control_id = -3
4327                      /* REVENUE ADJUSTMENTS DO NOT AFFECT REC OFFSET ROWS */
4328               and    g.rec_offset_flag IS NULL
4329                      /* ONLY ROUND RAM DISTRIBUTIONS */
4330               and    g.revenue_adjustment_id = t_rev_adj_id(i)
4331               /* END OF GL_DIST_ID SELECT */
4332               );
4333 
4334         END IF;
4335 
4336        l_rows_rounded_this_pass := 0;
4337 
4338        /* START - Cleanup loop */
4339        FOR upd in t_line_id.FIRST .. t_line_id.LAST LOOP
4340 
4341           IF(SQL%BULK_ROWCOUNT(upd) = 1)
4342           THEN
4343 
4344           /* This piece of code determines that 1 row was updated
4345              for each invoice line and account class.  Once the
4346              row is updated, we need to remove it from further
4347              consideration.  To do that, we change the line_id
4348              to line_id * -1 (a row that should never exist)
4349              and this prevents it from being processed in
4350              subsequent passes.
4351 
4352              Incidentally, I tried to just delete the
4353              processed rows - but this caused subsequent
4354              passes to fail with ORA errors due to missing
4355              plsql table rows.  The bulk update requires
4356              a continuous list in sequential order and, by deleting
4357              rows from the table, we cause the update to fail.
4358           */
4359 
4360 
4361               IF PG_DEBUG in ('Y', 'C') THEN
4362                  arp_standard.debug('  Target: ' || t_line_id(upd) ||
4363                                 '  ' || t_account_class(upd) ||
4364                                 '  ' || t_round_amount(upd) ||
4365                                 '  ' || t_round_acctd(upd) ||
4366                                 ' ' || t_round_percent(upd) ||
4367                                 ' ' || SQL%BULK_ROWCOUNT(upd));
4368               END IF;
4369 
4370               IF l_phase = 4
4371               THEN
4372                  /* extra checks to see if we need last phase */
4373                  IF t_round_amount(upd) = 0
4374                     OR  t_round_acctd(upd) = 0
4375                     OR  SIGN(t_round_amount(upd)) = SIGN(t_round_acctd(upd))
4376                  THEN
4377                     /* This phase inserted complete dists
4378                        so no need to insert another dist */
4379                     l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
4380                     t_line_id(upd) := -1 * t_line_id(upd);
4381                  ELSE
4382                     /* Do not change the line_id or increment.. this
4383                         forces the last phase and an insert of
4384                         a dist with amount=0 and acctd_amount=<correction * 2>
4385                     */
4386                     NULL;
4387                  END IF;
4388               ELSE
4389                  /* previous behavior */
4390                  l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
4391                  /* make line_id negative so it causes no further updates */
4392                  t_line_id(upd) := -1 * t_line_id(upd);
4393               END IF;
4394 
4395           END IF;
4396 
4397           IF(SQL%BULK_ROWCOUNT(upd) > 1)
4398           THEN
4399              /* Failure condition 1
4400                 This section of code executes only when more than
4401                 one line is updated for a given customer_trx_line_id
4402                 and account_class.  That would mean that the rounding
4403                 logic was unable to identify a single line for update
4404                 and rounding would then raise an error to roll back
4405                 any corrections or calculations for this transaction.
4406 
4407                 Revenue recognition has been modified to roll back
4408                 transactions that fail and to document the lines
4409                 that have problems.  */
4410 
4411              IF PG_DEBUG in ('Y', 'C')
4412              THEN
4413 
4414                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
4415                    arp_standard.debug(t_line_id(err)|| '  ' ||
4416                                       t_account_class(err) ||
4417                      '  ' || t_round_amount(err) ||
4418                      ' ' || t_round_acctd(err) || ' ' ||
4419                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
4420                 END LOOP;
4421 
4422              END IF;
4423 
4424              RETURN(iFALSE);
4425 
4426           END IF;
4427 
4428        END LOOP; /* END - Cleanup loop */
4429 
4430        IF PG_DEBUG in ('Y', 'C') THEN
4431           arp_standard.debug('    Rows rounded (this pass) : ' || l_rows_rounded_this_pass);
4432        END IF;
4433 
4434        l_rows_rounded := l_rows_rounded + l_rows_rounded_this_pass;
4435 
4436      END LOOP;  /* END - Main processing loop */
4437 
4438        IF (l_rows_needing_rounding <> l_rows_rounded) THEN
4439 
4440           /* Failure condition 2
4441              In this situation, the total number of distributions corrected
4442              does not match the number expected.  Because of condition 1
4443              handled above, this would only occur if we were unable to
4444              locate any rows to assess rounding corrections to for
4445              one or more invoice lines.  Such situations highlight
4446              shortcomings in this logic that must be investigated
4447              and corrected.
4448           */
4449 
4450           IF PG_DEBUG in ('Y', 'C') THEN
4451              arp_standard.debug('Mismatch between lines found and lines updated [see below]');
4452              arp_standard.debug('  Rows targeted: ' || l_rows_needing_rounding);
4453              arp_standard.debug('  Rows rounded : ' || l_rows_rounded);
4454 
4455              FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
4456 
4457                  arp_standard.debug(t_line_id(err) || '  ' || t_account_class(err) ||
4458                      '  ' || t_round_amount(err) || ' ' || t_round_acctd(err) || ' ' ||
4459                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
4460 
4461              END LOOP;
4462 
4463           END IF;
4464 
4465           RETURN(iFALSE);
4466        END IF;
4467 
4468        IF PG_DEBUG in ('Y', 'C') THEN
4469           arp_standard.debug('Total number of rows updated:  ' || l_rows_rounded);
4470        END IF;
4471 
4472   /* MRC Processing */
4473   IF PG_DEBUG in ('Y', 'C') THEN
4474      arp_standard.debug('doing rounding for MRC if necessary');
4475   END IF;
4476 
4477   /* This call to the MRC wrapper will eventually call a clone of this
4478      routine that was designed to round MRC gld table data.  The MRC
4479      call like the primary sob one utilizes the amounts and line_ids
4480      from ar_line_rev_adj_gt (global temporary table).
4481 
4482      Note that mrc_correct_rounding verifies that MRC is enabled before
4483      doing anything */
4484   ar_mrc_engine2.mrc_correct_rounding(
4485                    'CORRECT_REV_ADJ_BY_LINE',
4486                    NULL,    -- request_id
4487                    NULL,    -- customer_trx_id
4488                    NULL,    -- customer trx line id
4489                    NULL,
4490          	   NULL,    -- concat_segs
4491                    NULL,    -- balanced round_ccid
4492                    NULL,
4493                    NULL     -- period_set_name
4494                   );
4495   END IF;
4496 
4497   /* 9317102 - purge GT table to prevent re-processing of lines */
4498   DELETE from ar_line_rev_adj_gt;
4499 
4500   IF PG_DEBUG in ('Y', 'C') THEN
4501      arp_standard.debug('arp_rounding.correct_rev_adj_by_line()-');
4502   END IF;
4503 
4504   RETURN(iTRUE);
4505 END correct_rev_adj_by_line;
4506 
4507 /*-------------------------------------------------------------------------+
4508  | PRIVATE FUNCTION                                                        |
4509  | correct_line_level_rounding                                             |
4510  |                                                                         |
4511  | DESCRIPTION                                                             |
4512  | This function calls functions to correct rounding errors in             |
4513  | ra_cust_trx_line_gl_dist.                                               |
4514  |                                                                         |
4515  | REQUIRES                                                                |
4516  |   P_CUSTOMER_TRX_ID                                                     |
4517  |                                                                         |
4518  | RETURNS                                                                 |
4519  |   TRUE  if no errors occur                                              |
4520  |   FALSE otherwise.                                                      |
4521  |                                                                         |
4522  | NOTES                                                                   |
4523  |                                                                         |
4524  | EXAMPLE                                                                 |
4525  |                                                                         |
4526  | MODIFICATION HISTORY                                                    |
4527  |                                                                         |
4528  +-------------------------------------------------------------------------*/
4529 FUNCTION do_line_level_rounding(
4530                  P_REQUEST_ID            IN NUMBER,
4531                  P_CUSTOMER_TRX_ID       IN NUMBER,
4532                  P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
4533                  P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
4534                  P_ERROR_MESSAGE            OUT NOCOPY VARCHAR2,
4535                  P_BASE_PRECISION        IN NUMBER,
4536                  P_BASE_MIN_ACCOUNTABLE_UNIT IN NUMBER,
4537                  P_PERIOD_SET_NAME       IN OUT NOCOPY VARCHAR2,
4538                  P_CHECK_RULES_FLAG      IN VARCHAR2,
4539                  P_TRX_CLASS_TO_PROCESS  IN VARCHAR2,
4540                  P_FIX_REC_OFFSET        IN VARCHAR2 DEFAULT 'Y')
4541                  RETURN NUMBER IS
4542 
4543 begin
4544 
4545   IF PG_DEBUG in ('Y', 'C') THEN
4546      arp_standard.debug('arp_rounding.do_line_level_rounding()+ ' ||
4547                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4548   END IF;
4549 
4550     /*--------------------------------------------------------------+
4551      |  Correct each type of rounding error. Each function corrects |
4552      |  a different kind of error.                                  |
4553      +--------------------------------------------------------------*/
4554 
4555     /*--------------------------------------------------------------+
4556      |  Correct each type of rounding error. Each function corrects |
4557      |  a different kind of error.                                  |
4558      +--------------------------------------------------------------*/
4559 
4560    if ( correct_receivables_records( P_REQUEST_ID,
4561                                      P_CUSTOMER_TRX_ID,
4562                                      P_CUSTOMER_TRX_LINE_ID,
4563                                      P_ROWS_PROCESSED,
4564                                      P_ERROR_MESSAGE,
4565                                      P_BASE_PRECISION,
4566                                      P_BASE_MIN_ACCOUNTABLE_UNIT,
4567                                      P_TRX_CLASS_TO_PROCESS) = iFALSE)
4568    then return(iFALSE);
4569    end If;
4570 
4571 
4572    if ( correct_nonrule_line_records( P_REQUEST_ID,
4573                                       P_CUSTOMER_TRX_ID,
4574                                       P_CUSTOMER_TRX_LINE_ID,
4575                                       P_ROWS_PROCESSED,
4576                                       P_ERROR_MESSAGE,
4577                                       P_BASE_PRECISION,
4578                                       P_BASE_MIN_ACCOUNTABLE_UNIT,
4579                                       P_TRX_CLASS_TO_PROCESS) = iFALSE)
4580    then return(iFALSE);
4581    end If;
4582 
4583    if ( correct_rule_records_by_line( P_REQUEST_ID,
4584                               P_CUSTOMER_TRX_ID,
4585                               P_ROWS_PROCESSED,
4586                               P_ERROR_MESSAGE,
4587                               P_BASE_PRECISION,
4588                               P_BASE_MIN_ACCOUNTABLE_UNIT,
4589                               P_TRX_CLASS_TO_PROCESS,
4590                               P_CHECK_RULES_FLAG,
4591                               P_PERIOD_SET_NAME,
4592                               P_FIX_REC_OFFSET) = iFALSE)
4593    then return(iFALSE);
4594    end If;
4595 
4596    correct_suspense(p_customer_trx_id);
4597 
4598    IF PG_DEBUG in ('Y', 'C') THEN
4599       arp_standard.debug( 'arp_rounding.do_line_level_rounding()- ' ||
4600                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4601    END IF;
4602 
4603    return(iTRUE);
4604 
4605 end do_line_level_rounding;
4606 
4607 
4608 /*-------------------------------------------------------------------------+
4609  | PRIVATE FUNCTION                                                        |
4610  | replace_balancing_segment                                               |
4611  |                                                                         |
4612  | DESCRIPTION                                                             |
4613  |                                                                         |
4614  | This function accepts the REC and the ROUND code_combination_id,        |
4615  | replaces balancing segement of the ROUND accounting combination with    |
4616  | the REC segement and returns the new code_combination_id.               |
4617  |                                                                         |
4618  | REQUIRES                                                                |
4619  |                                                                         |
4620  | RETURNS                                                                 |
4621  |   TRUE  if no errors occur                                              |
4622  |   FALSE otherwise.                                                      |
4623  |                                                                         |
4624  | NOTES                                                                   |
4625  |                                                                         |
4626  | EXAMPLE                                                                 |
4627  |                                                                         |
4628  | MODIFICATION HISTORY                                                    |
4629  |      Satheesh Nambiar - 01/18/00                                        |
4630  |                         Bug 1152919. Added error_message as out NOCOPY         |
4631  |                         parameter to this private function              |
4632  +-------------------------------------------------------------------------*/
4633 
4634 FUNCTION replace_balancing_segment( original_ccid IN NUMBER,
4635                                     balancing_ccid IN NUMBER,
4636                                     return_ccid   OUT NOCOPY NUMBER,
4637                                     concat_segs   OUT NOCOPY VARCHAR2,
4638                                     error_message OUT NOCOPY VARCHAR2)
4639 RETURN NUMBER IS
4640 
4641 --concat_segs varchar2(240);
4642 concat_ids varchar2(2000);
4643 concat_descrs varchar2(2000);
4644 
4645 begin
4646 
4647    IF PG_DEBUG in ('Y', 'C') THEN
4648       arp_standard.debug( 'arp_rounding.replace_balancing_segment()+ ' ||
4649                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4650    END IF;
4651 
4652    if not AR_FLEXBUILDER_WF_PKG.SUBSTITUTE_BALANCING_SEGMENT(
4653                           arp_global.chart_of_accounts_id,
4654                           original_ccid,
4655                           balancing_ccid,
4656                           return_ccid,
4657                           concat_segs,
4658                           concat_ids,
4659                           concat_descrs,
4660                           error_message )
4661    then
4662 
4663       IF PG_DEBUG in ('Y', 'C') THEN
4664          arp_standard.debug('EXCEPTION:  substitute_balancing_segment failed ' ||
4665                            return_ccid);
4666       END IF;
4667       return(iFALSE);
4668    end if;
4669 
4670    IF PG_DEBUG in ('Y', 'C') THEN
4671       arp_standard.debug(' original_ccid: ' || original_ccid ||
4672                             ' balancing_ccid: ' || balancing_ccid ||
4673                             ' return_ccid: ' || return_ccid ||
4674                             ' concat_segs: ' || concat_segs
4675                       );
4676       arp_standard.debug( 'arp_rounding.replace_balancing_segment()- ' ||
4677                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4678    END IF;
4679 
4680    return(iTRUE);
4681 
4682 end replace_balancing_segment;
4683 
4684 /*-------------------------------------------------------------------------+
4685  | PRIVATE FUNCTION                                                        |
4686  | correct_header_level_rounding                                           |
4687  |                                                                         |
4688  | DESCRIPTION                                                             |
4689  | This function calls functions to correct rounding errors in             |
4690  | ra_cust_trx_line_gl_dist.                                               |
4691  |                                                                         |
4692  | REQUIRES                                                                |
4693  |   P_CUSTOMER_TRX_ID                                                     |
4694  |                                                                         |
4695  | RETURNS                                                                 |
4696  |   TRUE  if no errors occur                                              |
4697  |   FALSE otherwise.                                                      |
4698  |                                                                         |
4699  | NOTES                                                                   |
4700  |                                                                         |
4701  | EXAMPLE                                                                 |
4702  |                                                                         |
4703  | MODIFICATION HISTORY                                                    |
4704  |                                                                         |
4705  +-------------------------------------------------------------------------*/
4706 FUNCTION correct_header_level_rounding(
4707                  P_REQUEST_ID IN NUMBER,
4708                  P_CUSTOMER_TRX_ID           IN NUMBER,
4709                  P_CUSTOMER_TRX_LINE_ID      IN NUMBER,
4710                  P_ROWS_PROCESSED            IN OUT NOCOPY NUMBER,
4711                  P_ERROR_MESSAGE            OUT NOCOPY VARCHAR2,
4712                  P_BASE_PRECISION            IN NUMBER,
4713                  P_BASE_MIN_ACCOUNTABLE_UNIT IN NUMBER,
4714                  P_PERIOD_SET_NAME           IN OUT NOCOPY VARCHAR2,
4715                  P_CHECK_RULES_FLAG          IN VARCHAR2,
4716                  P_TRX_CLASS_TO_PROCESS      IN VARCHAR2,
4717                  P_REC_CODE_COMBINATION_ID   IN NUMBER,
4718                  P_TRX_HEADER_ROUND_CCID     IN NUMBER,
4719                  P_FIX_REC_OFFSET            IN VARCHAR2 DEFAULT 'Y')
4720 RETURN NUMBER IS
4721 
4722 balanced_round_ccid number;
4723 concat_segs varchar2(240);
4724 
4725 begin
4726 
4727   IF PG_DEBUG in ('Y', 'C') THEN
4728      arp_standard.debug('arp_rounding.correct_header_level_rounding()+ ' ||
4729                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4730   END IF;
4731 
4732     /*--------------------------------------------------------------+
4733      |  Correct each type of rounding error. Each function corrects |
4734      |  a different kind of error.                                  |
4735      +--------------------------------------------------------------*/
4736 
4737    if ( correct_receivables_header( P_REQUEST_ID,
4738                                     P_CUSTOMER_TRX_ID,
4739                                     P_CUSTOMER_TRX_LINE_ID,
4740                                     P_ROWS_PROCESSED,
4741                                     P_ERROR_MESSAGE,
4742                                     P_BASE_PRECISION,
4743                                     P_BASE_MIN_ACCOUNTABLE_UNIT,
4744                                     P_TRX_CLASS_TO_PROCESS) = iFALSE)
4745    then return(iFALSE);
4746    end If;
4747 
4748 
4749    if ( correct_nonrule_line_records( P_REQUEST_ID,
4750                                       P_CUSTOMER_TRX_ID,
4751                                       P_CUSTOMER_TRX_LINE_ID,
4752                                       P_ROWS_PROCESSED,
4753                                       P_ERROR_MESSAGE,
4754                                       P_BASE_PRECISION,
4755                                       P_BASE_MIN_ACCOUNTABLE_UNIT,
4756                                       P_TRX_CLASS_TO_PROCESS) = iFALSE)
4757    then return(iFALSE);
4758    end If;
4759 
4760    if ( correct_rule_records_by_line( P_REQUEST_ID,
4761                               P_CUSTOMER_TRX_ID,
4762                               P_ROWS_PROCESSED,
4763                               P_ERROR_MESSAGE,
4764                               P_BASE_PRECISION,
4765                               P_BASE_MIN_ACCOUNTABLE_UNIT,
4766                               P_TRX_CLASS_TO_PROCESS,
4767                               P_CHECK_RULES_FLAG,
4768                               P_PERIOD_SET_NAME,
4769                               P_FIX_REC_OFFSET) = iFALSE)
4770    then return(iFALSE);
4771    end If;
4772 
4773    --Bug 954681 and 1158340: Call the replace_balancing_segment routine
4774    --only if the REC ccid is valid.
4775   IF P_REC_CODE_COMBINATION_ID  > -1  THEN
4776 
4777    if ( replace_balancing_segment( P_TRX_HEADER_ROUND_CCID,
4778                                    P_REC_CODE_COMBINATION_ID,
4779                                    balanced_round_ccid,
4780                                    CONCAT_SEGS ,
4781                                    P_ERROR_MESSAGE) = iFALSE)
4782    then
4783     return(iFALSE);
4784    end If;
4785   END IF;
4786 
4787    /*--------------------------------------------------------------+
4788     |  If the balanced_round_ccid is returned as -1 then           |
4789     |  it gets the value of p_trx_header_round_ccid which is valid |
4790     |  code combination id as opposed to -1                        |
4791     +--------------------------------------------------------------*/
4792    /* Bug 5707676. if P_REC_CODE_COMBINATION_ID is -1 then balanced_round_ccid will NOT be initialized. So put NVL in if clause */
4793 
4794    if ( nvl(balanced_round_ccid,-1) = -1)
4795 
4796    then
4797         balanced_round_ccid := P_TRX_HEADER_ROUND_CCID;
4798    end if;
4799 
4800    if ( correct_round_records( P_REQUEST_ID,
4801                                P_CUSTOMER_TRX_ID,
4802                                P_CUSTOMER_TRX_LINE_ID,
4803                                P_ROWS_PROCESSED,
4804                                P_ERROR_MESSAGE,
4805                                P_BASE_PRECISION,
4806                                P_BASE_MIN_ACCOUNTABLE_UNIT,
4807                                P_TRX_CLASS_TO_PROCESS,
4808                                CONCAT_SEGS,
4809                                BALANCED_ROUND_CCID) = iFALSE)
4810    then return(iFALSE);
4811    end If;
4812 
4813    IF PG_DEBUG in ('Y', 'C') THEN
4814       arp_standard.debug( 'arp_rounding.correct_header_level_rounding()- ' ||
4815                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4816    END IF;
4817 
4818    return(iTRUE);
4819 
4820 end correct_header_level_rounding;
4821 
4822 PROCEDURE get_select_column_values(
4823         P_SELECT_SQL_C   IN INTEGER,
4824         P_SELECT_REC IN OUT NOCOPY SELECT_REC_TYPE ) IS
4825 BEGIN
4826 
4827     IF PG_DEBUG in ('Y', 'C') THEN
4828        arp_standard.debug( 'arp_rounding.get_select_column_values()+' );
4829     END IF;
4830 
4831     dbms_sql.column_value( p_select_sql_c, 1,
4832                            p_select_rec.rec_customer_trx_id);
4833     dbms_sql.column_value( p_select_sql_c, 2,
4834                            p_select_rec.rec_code_combination_id);
4835     dbms_sql.column_value( p_select_sql_c, 3,
4836                            p_select_rec.round_customer_trx_id);
4837 
4838     IF PG_DEBUG in ('Y', 'C') THEN
4839        arp_standard.debug( 'arp_rounding.get_select_column_values()-' );
4840     END IF;
4841 
4842 EXCEPTION
4843     WHEN OTHERS THEN
4844         IF PG_DEBUG in ('Y', 'C') THEN
4845            arp_standard.debug('EXCEPTION: arp_rounding.get_select_column_values()');
4846         END IF;
4847         RAISE;
4848 END get_select_column_values;
4849 
4850 PROCEDURE dump_select_rec( P_SELECT_REC IN SELECT_REC_TYPE ) IS
4851 BEGIN
4852 
4853     IF PG_DEBUG in ('Y', 'C') THEN
4854        arp_standard.debug( 'arp_rounding.dump_select_rec()+' );
4855        arp_standard.debug('  Dumping select record: ');
4856        arp_standard.debug('  rec_customer_trx_id=' ||
4857                  p_select_rec.rec_customer_trx_id);
4858        arp_standard.debug('  rec_code_combination_id=' ||
4859                  p_select_rec.rec_code_combination_id);
4860        arp_standard.debug('  round_customer_trx_id=' ||
4861                  p_select_rec.round_customer_trx_id);
4862        arp_standard.debug( 'arp_rounding.dump_select_rec()-' );
4863     END IF;
4864 
4865 EXCEPTION
4866     WHEN OTHERS THEN
4867        IF PG_DEBUG in ('Y', 'C') THEN
4868           arp_standard.debug( 'EXCEPTION: arp_rounding.dump_select_rec()' );
4869        END IF;
4870         RAISE;
4871 END dump_select_rec;
4872 
4873 
4874 PROCEDURE define_columns( P_SELECT_SQL_C IN INTEGER,
4875                           P_SELECT_REC IN SELECT_REC_TYPE) IS
4876 BEGIN
4877 
4878     arp_standard.debug( 'arp_rounding.define_columns()+' );
4879 
4880     ------------------------------------------------------------
4881     -- Define columns
4882     ------------------------------------------------------------
4883         arp_standard.debug( '  Defining columns for select_sql_c');
4884 
4885         dbms_sql.define_column( p_select_sql_c, 1,
4886                                 p_select_rec.rec_customer_trx_id );
4887         dbms_sql.define_column( p_select_sql_c, 2,
4888                                 p_select_rec.rec_code_combination_id );
4889         dbms_sql.define_column( p_select_sql_c, 3,
4890                                 p_select_rec.round_customer_trx_id );
4891 
4892     arp_standard.debug( 'arp_rounding.define_columns()-' );
4893 
4894 EXCEPTION
4895    WHEN OTHERS THEN
4896         arp_standard.debug( 'EXCEPTION: Error defining columns for select_sql_c' );
4897         RAISE;
4898 END;
4899 
4900 
4901 PROCEDURE build_select_sql(
4902                            P_REQUEST_ID IN INTEGER,
4903                            P_CUSTOMER_TRX_ID IN INTEGER,
4904                            P_SELECT_SQL_C IN OUT NOCOPY INTEGER  ) IS
4905 
4906     l_select_sql   VARCHAR2(1000);
4907     l_where_pred   VARCHAR2(500);
4908 
4909 BEGIN
4910 
4911     IF PG_DEBUG in ('Y', 'C') THEN
4912        arp_standard.debug( 'arp_rounding.build_select_sql()+' );
4913     END IF;
4914 
4915     ------------------------------------------------
4916     -- Construct where predicate
4917     ------------------------------------------------
4918 
4919     IF ( p_customer_trx_id IS NOT NULL ) THEN
4920         ----------------------------------------------------
4921         -- Passed customer_trx_id
4922         ----------------------------------------------------
4923 
4924         l_where_pred :=
4925 'AND rec.customer_trx_id = :p_customer_trx_id ';
4926     ELSE
4927 
4928         l_where_pred :=
4929 'AND rec.request_id = :p_request_id ';
4930 
4931     END IF;
4932 
4933     l_select_sql :=
4934 'select rec.customer_trx_id,
4935 rec.code_combination_id,
4936 round.customer_trx_id
4937 from
4938 ra_cust_trx_line_gl_dist rec,
4939 ra_cust_trx_line_gl_dist round
4940 where
4941 rec.customer_trx_id = round.customer_trx_id(+)
4942 and    rec.account_set_flag = round.account_set_flag(+)' ||
4943 l_where_pred  ||
4944 'and    rec.account_class = ''REC''
4945 and    rec.latest_rec_flag = ''Y''
4946 and    round.account_class(+) = ''ROUND''';
4947 
4948    IF PG_DEBUG in ('Y', 'C') THEN
4949       arp_standard.debug('select_sql =  ' ||
4950                        l_select_sql);
4951    END IF;
4952 
4953     ------------------------------------------------
4954     -- Parse sql stmts
4955     ------------------------------------------------
4956 
4957    BEGIN
4958         IF PG_DEBUG in ('Y', 'C') THEN
4959            arp_standard.debug('Parsing select stmt');
4960         END IF;
4961 
4962         p_select_sql_c := dbms_sql.open_cursor;
4963         dbms_sql.parse( p_select_sql_c, l_select_sql, dbms_sql.v7 );
4964 
4965         IF ( p_customer_trx_id IS NOT NULL ) THEN
4966             ----------------------------------------------------
4967             -- Passed customer_trx_id
4968             ----------------------------------------------------
4969             dbms_sql.bind_variable(p_select_sql_c, ':p_customer_trx_id', p_customer_trx_id);
4970 
4971         ELSE
4972 
4973             dbms_sql.bind_variable(p_select_sql_c, ':p_request_id', p_request_id);
4974 
4975         END IF;
4976 
4977     EXCEPTION
4978       WHEN OTHERS THEN
4979           IF PG_DEBUG in ('Y', 'C') THEN
4980              arp_standard.debug('build_select_sql: ' ||  'EXCEPTION: Error parsing select stmt' );
4981           END IF;
4982           RAISE;
4983     END;
4984 
4985     IF PG_DEBUG in ('Y', 'C') THEN
4986        arp_standard.debug( 'arp_rounding.build_select_sql()-' );
4987     END IF;
4988 
4989 
4990 EXCEPTION
4991     WHEN OTHERS THEN
4992         IF PG_DEBUG in ('Y', 'C') THEN
4993            arp_standard.debug( 'EXCEPTION: arp_rounding.build_select_sql()' );
4994         END IF;
4995 
4996         RAISE;
4997 END build_select_sql;
4998 /*-------------------------------------------------------------------------+
4999  | PRIVATE FUNCTION                                                        |
5000  | do_header_level_rounding                                                |
5001  |                                                                         |
5002  | DESCRIPTION                                                             |
5003  |   This function inserts a record of account_class = ROUND into          |
5004  |   ra_cust_trx_line_gl_dist table. If the transaction was created before |
5005  |   setting the header level rounding option On then this function will   |
5006  |   insert the round record only if there is no activity on it otherwise  |
5007  |   it will do the release 10 rounding (do_line_level_rounding).          |
5008  |   Also if arp_rounding is called from revenue recognition program then  |
5009  |   this function will not insert the ROUND record but revenue recognition|
5010  |   will insert it.                                                       |
5011  |                                                                         |
5012  | REQUIRES                                                                |
5013  |   P_REQUEST_ID, P_CUSTOMER_TRX_ID                                       |
5014  |                                                                         |
5015  | RETURNS                                                                 |
5016  |   TRUE  if no errors occur                                              |
5017  |   FALSE otherwise.                                                      |
5018  |                                                                         |
5019  | NOTES                                                                   |
5020  |                                                                         |
5021  | EXAMPLE                                                                 |
5022  |                                                                         |
5023  | MODIFICATION HISTORY                                                    |
5024  |                                                                         |
5025  +-------------------------------------------------------------------------*/
5026 
5027 FUNCTION do_header_level_rounding
5028                  ( P_REQUEST_ID                    IN NUMBER,
5029                    P_CUSTOMER_TRX_ID               IN NUMBER,
5030                    P_CUSTOMER_TRX_LINE_ID          IN NUMBER,
5031                    P_ROWS_PROCESSED            IN OUT NOCOPY NUMBER,
5032                    P_ERROR_MESSAGE                OUT NOCOPY VARCHAR2,
5033                    P_BASE_PRECISION                IN NUMBER,
5034                    P_BASE_MIN_ACCOUNTABLE_UNIT     IN VARCHAR2,
5035                    P_TRX_CLASS_TO_PROCESS          IN VARCHAR2,
5036                    P_PERIOD_SET_NAME           IN OUT NOCOPY VARCHAR2,
5037                    P_CHECK_RULES_FLAG              IN VARCHAR2,
5038                    P_TRX_HEADER_LEVEL_ROUNDING     IN VARCHAR2,
5039                    P_ACTIVITY_FLAG                 IN VARCHAR2,
5040                    P_TRX_HEADER_ROUND_CCID         IN NUMBER,
5041                    P_FIX_REC_OFFSET                IN VARCHAR2 DEFAULT 'Y'
5042                  )
5043 RETURN NUMBER IS
5044 
5045   l_select_rec              select_rec_type;
5046   l_null_rec       CONSTANT select_rec_type := l_select_rec;
5047   l_ignore                  INTEGER;
5048   l_request_id              INTEGER;
5049   l_customer_trx_id         INTEGER;
5050 
5051 begin
5052 
5053  /* bug 912501 : Added 'G' for the possible values of p_activity_flag */
5054    if (p_activity_flag = 'Y' OR p_activity_flag = 'G') OR (p_check_rules_flag = 'Y' )
5055    then
5056       NULL;
5057    else
5058       if ( insert_round_records( P_REQUEST_ID,
5059                                  P_CUSTOMER_TRX_ID,
5060                                  P_ROWS_PROCESSED,
5061                                  P_ERROR_MESSAGE,
5062                                  P_BASE_PRECISION,
5063                                  P_BASE_MIN_ACCOUNTABLE_UNIT,
5064                                  P_TRX_CLASS_TO_PROCESS,
5065                                  P_TRX_HEADER_ROUND_CCID) = iFALSE)
5066       then return(iFALSE);
5067       end if;
5068    end if;
5069 
5070 
5071    -----------------------------------------------------------------------
5072    -- Create dynamic sql
5073    -----------------------------------------------------------------------
5074    IF PG_DEBUG in ('Y', 'C') THEN
5075      arp_standard.debug('  Creating dynamic sql');
5076   END IF;
5077 
5078    build_select_sql( P_REQUEST_ID,
5079                      P_CUSTOMER_TRX_ID,
5080                      SELECT_SQL_C);
5081 
5082    -----------------------------------------------------------
5083    -- Define columns
5084    -----------------------------------------------------------
5085    define_columns( select_sql_c, l_select_rec );
5086 
5087    ---------------------------------------------------------------
5088    -- Execute sql
5089    ---------------------------------------------------------------
5090    IF PG_DEBUG in ('Y', 'C') THEN
5091       arp_standard.debug('  Executing select sql' );
5092    END IF;
5093 
5094    BEGIN
5095        l_ignore := dbms_sql.execute( select_sql_c );
5096 
5097    EXCEPTION
5098       WHEN OTHERS THEN
5099             IF PG_DEBUG in ('Y', 'C') THEN
5100                arp_standard.debug('EXCEPTION: Error executing select sql' );
5101             END IF;
5102             RAISE;
5103    END;
5104 
5105    --------------------------------------------------------------
5106    -- Fetch rows
5107    --------------------------------------------------------------
5108    IF PG_DEBUG in ('Y', 'C') THEN
5109       arp_standard.debug('  Fetching select stmt');
5110    END IF;
5111 
5112    begin
5113       loop
5114          if (dbms_sql.fetch_rows( select_sql_c ) > 0)
5115          then
5116 
5117             IF PG_DEBUG in ('Y', 'C') THEN
5118                arp_standard.debug('  fetched a row' );
5119             END IF;
5120             l_select_rec := l_null_rec;
5121             ------------------------------------------------------
5122             -- Get column values
5123             ------------------------------------------------------
5124             get_select_column_values( select_sql_c, l_select_rec );
5125 
5126             dump_select_rec( l_select_rec );
5127          else
5128             IF PG_DEBUG in ('Y', 'C') THEN
5129                arp_standard.debug(   '  Done fetching');
5130             END IF;
5131             EXIT;
5132          end if;
5133 
5134        -- further processing.
5135 
5136          l_customer_trx_id := l_select_rec.rec_customer_trx_id;
5137 
5138          IF PG_DEBUG in ('Y', 'C') THEN
5139             arp_standard.debug(  'rec_customer_trx_id: '||  l_customer_trx_id);
5140          END IF;
5141 
5142          if (l_select_rec.round_customer_trx_id is null)
5143          then
5144             -- ROUND record does not exist for this transaction
5145             -- This means the transaction was created before
5146             -- setting TRX_HEADER_LEVEL_ROUNDING ON
5147             -- Round the transaction with release 10 method
5148 
5149             if ( do_line_level_rounding( l_REQUEST_ID,
5150                                          l_CUSTOMER_TRX_ID,
5151                                          P_CUSTOMER_TRX_LINE_ID,
5152                                          P_ROWS_PROCESSED,
5153                                          P_ERROR_MESSAGE,
5154                                          P_BASE_PRECISION,
5155                                          P_BASE_MIN_ACCOUNTABLE_UNIT,
5156                                          P_PERIOD_SET_NAME,
5157                                          P_CHECK_RULES_FLAG,
5158                                          P_TRX_CLASS_TO_PROCESS,
5159                                          P_FIX_REC_OFFSET) = iFALSE)
5160             then return(iFALSE);
5161             end If;
5162          else
5163             if ( correct_header_level_rounding( l_REQUEST_ID,
5164                                                 l_CUSTOMER_TRX_ID,
5165                                                 P_CUSTOMER_TRX_LINE_ID,
5166                                                 P_ROWS_PROCESSED,
5167                                                 P_ERROR_MESSAGE,
5168                                                 P_BASE_PRECISION,
5169                                                 P_BASE_MIN_ACCOUNTABLE_UNIT,
5170                                                 P_PERIOD_SET_NAME,
5171                                                 P_CHECK_RULES_FLAG,
5172                                                 P_TRX_CLASS_TO_PROCESS,
5173                                         l_select_rec.rec_code_combination_id,
5174                                         P_TRX_HEADER_ROUND_CCID) = iFALSE)
5175             then return(iFALSE);
5176             end If;
5177          end if;
5178       end loop;
5179 --Bug 1777081:Close the cursor to avoid the maximum cursor exceeding error.
5180 
5181       dbms_sql.close_cursor(select_sql_c);
5182    end;
5183 
5184    IF PG_DEBUG in ('Y', 'C') THEN
5185       arp_standard.debug( 'arp_rounding.do_header_level_rounding()- ' ||
5186                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
5187    END IF;
5188 
5189    return(iTRUE);
5190 
5191 end do_header_level_rounding;
5192 
5193 
5194 /*-------------------------------------------------------------------------+
5195  | PUBLIC FUNCTION                                                         |
5196  |   correct_dist_rounding_errors()                                        |
5197  |                                                                         |
5198  | DESCRIPTION                                                             |
5199  |   This function corrects all rounding errors in the                     |
5200  |   ra_cust_trx_line_gl_dist table.                                       |
5201  |                                                                         |
5202  | REQUIRES                                                                |
5203  |   P_REQUEST_ID, P_CUSTOMER_TRX_ID or P_CUSTOMER_TRX_LINE_ID             |
5204  |   If header level rounding is enforced then requires either of          |
5205  |   P_REQUEST_ID, P_CUSTOMER_TRX_ID.                                      |
5206  |                                                                         |
5207  | RETURNS                                                                 |
5208  |   TRUE  if no errors occur                                              |
5209  |   FALSE otherwise.                                                      |
5210  |                                                                         |
5211  | NOTES                                                                   |
5212  |                                                                         |
5213  | EXAMPLE                                                                 |
5214  |                                                                         |
5215  | MODIFICATION HISTORY                                                    |
5216  |   03-AUG-2002  MRAYMOND   Added p_fix_rec_offset parameter to indicate
5217  |                            when to run the fix logic.
5218  +-------------------------------------------------------------------------*/
5219 
5220 FUNCTION correct_dist_rounding_errors
5221                  ( P_REQUEST_ID                    IN NUMBER,
5222                    P_CUSTOMER_TRX_ID               IN NUMBER,
5223                    P_CUSTOMER_TRX_LINE_ID          IN NUMBER,
5224                    P_ROWS_PROCESSED                IN OUT NOCOPY NUMBER,
5225                    P_ERROR_MESSAGE                 OUT NOCOPY VARCHAR2,
5226                    P_BASE_PRECISION                IN NUMBER,
5227                    P_BASE_MIN_ACCOUNTABLE_UNIT     IN VARCHAR2,
5228                    P_TRX_CLASS_TO_PROCESS          IN VARCHAR2  DEFAULT 'ALL',
5229                    P_CHECK_RULES_FLAG              IN VARCHAR2  DEFAULT 'N',
5230                    P_DEBUG_MODE                    IN VARCHAR2,
5231                    P_TRX_HEADER_LEVEL_ROUNDING     IN VARCHAR2  DEFAULT 'N',
5232                    P_ACTIVITY_FLAG                 IN VARCHAR2  DEFAULT 'N',
5233                    P_FIX_REC_OFFSET                IN VARCHAR2  DEFAULT 'Y'
5234                  )
5235 	RETURN NUMBER IS
5236 
5237   base_precision            NUMBER;
5238   base_min_accountable_unit NUMBER;
5239   trx_class_to_process      VARCHAR2(15);
5240   check_rules_flag          VARCHAR2(2);
5241   period_set_name           VARCHAR2(15);
5242   trx_header_round_ccid     number;
5243   l_select_rec              select_rec_type;
5244   l_null_rec       CONSTANT select_rec_type := l_select_rec;
5245   l_ignore                  INTEGER;
5246   activity_flag             VARCHAR2(1);
5247   l_rec_amt number;
5248   l_rec_acctd_amt number;
5249   l_actual_acctd_amt NUMBER;
5250   l_count NUMBER;
5251 
5252 BEGIN
5253 
5254   /*-------------------------------------------------------+
5255    |  Set a savepoint to rollback to if the function fails |
5256    +-------------------------------------------------------*/
5257 
5258    SAVEPOINT ARPLBCRE_1;
5259 
5260    IF ( do_setup(
5261                  P_REQUEST_ID,
5262                  P_CUSTOMER_TRX_ID,
5263                  P_CUSTOMER_TRX_LINE_ID,
5264                  P_BASE_PRECISION,
5265                  P_BASE_MIN_ACCOUNTABLE_UNIT,
5266                  P_TRX_CLASS_TO_PROCESS,
5267                  P_CHECK_RULES_FLAG,
5268                  P_DEBUG_MODE,
5269                  BASE_PRECISION,
5270                  BASE_MIN_ACCOUNTABLE_UNIT,
5271                  TRX_CLASS_TO_PROCESS,
5272                  CHECK_RULES_FLAG,
5273                  PERIOD_SET_NAME,
5274                  P_ROWS_PROCESSED,
5275                  P_ERROR_MESSAGE,
5276                  P_TRX_HEADER_LEVEL_ROUNDING,
5277                  P_ACTIVITY_FLAG,
5278                  ACTIVITY_FLAG,
5279                  TRX_HEADER_ROUND_CCID
5280                ) = iFALSE )
5281    THEN
5282        RETURN( iFALSE );
5283    END IF;
5284 
5285 
5286    /*----------------------------------------------+
5287     |  Print out NOCOPY the parameters in debug mode only |
5288     +----------------------------------------------*/
5289 
5290    IF PG_DEBUG in ('Y', 'C') THEN
5291       arp_standard.debug( 'arp_rounding.correct_dist_rounding_errors()+ ' ||
5292                       TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
5293       arp_standard.debug('  Request_id: ' || p_request_id ||
5294                      ' ctid: '|| p_customer_trx_id ||'  ctlid: '||
5295                      p_customer_trx_line_id || '  class: ' ||
5296                      trx_class_to_process || '  Rules: '||
5297                      check_rules_flag);
5298       arp_standard.debug(' Precision: ' || base_precision ||
5299                      '  MAU: ' || base_min_accountable_unit ||
5300                      '  Period Set: '|| period_set_name);
5301       arp_standard.debug('p_trx_header_level_rounding: ' ||
5302                      p_trx_header_level_rounding || ' p_activity_flag:' ||
5303                      p_activity_flag || ' trx_header_round_ccid:' ||
5304                      trx_header_round_ccid);
5305    END IF;
5306 
5307     /*--------------------------------------------------------------+
5308      |  Correct each type of rounding error. Each function corrects |
5309      |  a different kind of error.                                  |
5310      +--------------------------------------------------------------*/
5311 
5312 
5313    if (p_trx_header_level_rounding = 'Y')
5314    then
5315       if ( do_header_level_rounding( P_REQUEST_ID,
5316                                      P_CUSTOMER_TRX_ID,
5317                                      P_CUSTOMER_TRX_LINE_ID,
5318                                      P_ROWS_PROCESSED,
5319                                      P_ERROR_MESSAGE,
5320                                      BASE_PRECISION,
5321                                      BASE_MIN_ACCOUNTABLE_UNIT,
5322                                      TRX_CLASS_TO_PROCESS,
5323                                      PERIOD_SET_NAME,
5324                                      CHECK_RULES_FLAG,
5325                                      P_TRX_HEADER_LEVEL_ROUNDING,
5326                                      ACTIVITY_FLAG,
5327                                      TRX_HEADER_ROUND_CCID,
5328                                      P_FIX_REC_OFFSET) = iFALSE)
5329       then return(iFALSE);
5330       end if;
5331    else
5332       /* Do the release 10 rounding */
5333       if ( do_line_level_rounding( P_REQUEST_ID,
5334                                    P_CUSTOMER_TRX_ID,
5335                                    P_CUSTOMER_TRX_LINE_ID,
5336                                    P_ROWS_PROCESSED,
5337                                    P_ERROR_MESSAGE,
5338                                    BASE_PRECISION,
5339                                    BASE_MIN_ACCOUNTABLE_UNIT,
5340                                    PERIOD_SET_NAME,
5341                                    CHECK_RULES_FLAG,
5342                                    TRX_CLASS_TO_PROCESS,
5343                                    P_FIX_REC_OFFSET) = iFALSE)
5344       then return(iFALSE);
5345       end if;
5346 
5347 	/* Start - Bug 13090600 */
5348 
5349 	l_rec_amt :=0 ;
5350 	l_rec_acctd_amt := 0;
5351 	l_actual_acctd_amt :=0;
5352 
5353 	BEGIN
5354 
5355 	SELECT line_dist.acctd_amount,line_dist.amount,
5356 	arpcurr.currround(line_dist.amount * nvl(ct.exchange_rate,1),ct.	invoice_currency_code)
5357 	 INTO l_rec_acctd_amt,l_rec_amt,l_actual_acctd_amt
5358 	 FROM ra_cust_trx_line_gl_dist line_dist,
5359 	      ra_customer_trx ct
5360 	 WHERE line_dist.customer_trx_id = ct.customer_trx_id
5361 	 AND line_dist.customer_trx_id = p_customer_trx_id
5362 	 AND line_dist.account_class = 'REC'
5363 	 AND line_dist.account_set_flag = 'N'
5364 	 AND line_dist.latest_rec_flag = 'Y'
5365 	 AND ct.invoicing_rule_id is NULL;
5366 
5367 	IF SIGN(l_rec_amt) <> SIGN(l_rec_acctd_amt) AND l_rec_amt <> 0 AND l_rec_acctd_amt <> 0 THEN
5368 
5369 	UPDATE ra_cust_trx_line_gl_dist
5370 	SET acctd_amount =  acctd_amount -
5371 	Decode(Sign(l_rec_acctd_amt),-1 ,(Abs(l_actual_acctd_amt)-Abs(l_rec_acctd_amt)),(l_rec_acctd_amt - l_actual_acctd_amt))
5372 	WHERE cust_trx_line_gl_dist_id =
5373   	(SELECT MAX(cust_trx_line_gl_dist_id)
5374    		FROM ra_cust_trx_line_gl_dist
5375    		WHERE customer_trx_id = p_customer_trx_id
5376    		AND account_class = 'REV'
5377    		AND account_set_flag = 'N'
5378    		AND sign(acctd_amount) = Decode(Sign(l_rec_acctd_amt),-1,
5379 		sign(Abs(l_actual_acctd_amt)-Abs(l_rec_acctd_amt)),sign(l_rec_acctd_amt - l_actual_acctd_amt)));
5380 
5381   	l_count := sql%ROWCOUNT;
5382 
5383 	If (l_count > 0) THEN
5384 
5385 	UPDATE ra_cust_trx_line_gl_dist
5386 		SET acctd_amount = l_actual_acctd_amt
5387 		WHERE customer_trx_id = p_customer_trx_id
5388 		AND account_class = 'REC'
5389 		AND account_set_flag = 'N'
5390 		AND latest_rec_flag = 'Y';
5391 
5392 	END IF;
5393 
5394 	END IF;
5395 	EXCEPTION
5396 		 WHEN NO_DATA_FOUND THEN
5397 		    arp_standard.debug('REC record does not exist to adjust the amount');
5398 	END;
5399 
5400 	/* End - Bug 13090600 */
5401    end if;
5402 
5403    IF PG_DEBUG in ('Y', 'C') THEN
5404       arp_standard.debug( 'arp_rounding.correct_dist_rounding_errors()- ' ||
5405                       TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
5406    END IF;
5407 
5408    RETURN( iTRUE );
5409 
5410   /*---------------------------------------------------------------------+
5411    |  If any of the functions encounter an ORACLE error, that error is   |
5412    |  trapped here. The message is copied into the error_message         |
5413    |  parameter, and the function rolls back and returns FALSE.          |
5414    +---------------------------------------------------------------------*/
5415 
5416 EXCEPTION
5417    WHEN OTHERS THEN
5418         p_error_message := SQLERRM;
5419 
5420         ROLLBACK TO SAVEPOINT ARPLBCRE_1;
5421 
5422         IF PG_DEBUG in ('Y', 'C') THEN
5423            arp_standard.debug( 'arp_rounding.correct_dist_rounding_errors()+ ' ||
5424                          TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
5425         END IF;
5426 
5427         RETURN( iFALSE );
5428 
5429 
5430 END correct_dist_rounding_errors;
5431 
5432 /*-------------------------------------------------------------------------+
5433  | PUBLIC PROCEDURE                                                        |
5434  |   correct_scredit_rounding_errs()                                       |
5435  |                                                                         |
5436  | DESCRIPTION                                                             |
5437  |   This function corrects all rounding errors in the                     |
5438  |   ra_cust_trx_line_salesreps table.                                     |
5439  |                                                                         |
5440  | REQUIRES                                                                |
5441  |   P_CUSTOMER_TRX_ID							   |
5442  |                                                                         |
5443  | NOTES                                                                   |
5444  |                                                                         |
5445  | EXAMPLE                                                                 |
5446  |                                                                         |
5447  | MODIFICATION HISTORY                                                    |
5448  |   30-AUG-95  Charlie Tomberg       Created                              |
5449  |   03-OCT-03  M Raymond      Bug 3155664 - commented out nonrev scredit
5450  |                             rounding logic (it was ineffective)
5451  |                             and modified rev scredit logic to avoid
5452  |                             ORA-979 errors.
5453  +-------------------------------------------------------------------------*/
5454 
5455 PROCEDURE correct_scredit_rounding_errs( p_customer_trx_id   IN NUMBER,
5456                                          p_rows_processed   OUT NOCOPY NUMBER
5457                                          ) IS
5458 
5459   l_count number;
5460 
5461 BEGIN
5462 
5463   /*-------------------------------------------------------+
5464    |  Set a savepoint to rollback to if the function fails |
5465    +-------------------------------------------------------*/
5466 
5467    SAVEPOINT ARPLBCRE_2;
5468 
5469    arp_util.print_fcn_label( 'arp_rounding.correct_scredit_rounding_errs()+ ');
5470 
5471  /*-------------------------------------------------------------------------+
5472   |  Correct errors in the revenue_amount_split and revenue_percent_split   |
5473   |  columns:                                                               |
5474   |                                                                         |
5475   |    - Insure that the sum of the revenue percents equals 100 if the sum  |
5476   |      of the revenue amounts equals the line amount.                     |
5477   |    - Insure that the sum of revenue amounts equals the line amount if   |
5478   |      the sum of the revenue percents equals 100.                        |
5479   +-------------------------------------------------------------------------*/
5480 
5481    UPDATE ra_cust_trx_line_salesreps ctls
5482    SET     (
5483               ctls.revenue_amount_split,
5484               ctls.revenue_percent_split
5485            ) =
5486            (
5487              SELECT ctls.revenue_amount_split +
5488                     (
5489                        ctl1.extended_amount -
5490                        SUM(
5491                              NVL(ctls1.revenue_amount_split, 0)
5492                           )
5493                     ),
5494                     ctls.revenue_percent_split +
5495                     (
5496                        100 -
5497                        SUM(
5498                              NVL(ctls1.revenue_percent_split, 0)
5499                           )
5500                     )
5501              FROM     ra_customer_trx_lines ctl1,
5502                       ra_cust_trx_line_salesreps ctls1
5503              WHERE    ctl1.customer_trx_line_id = ctls1.customer_trx_line_id
5504              AND      ctls.customer_trx_line_id = ctls1.customer_trx_line_id
5505              GROUP BY ctls1.customer_trx_line_id,
5506                       ctl1.extended_amount,
5507                       ctls.revenue_amount_split,
5508                       ctls.revenue_percent_split
5509            )
5510    WHERE   ctls.cust_trx_line_salesrep_id in
5511            (
5512              SELECT   MIN(cust_trx_line_salesrep_id)
5513              FROM     ra_cust_trx_line_salesreps ctls,
5514                       ra_customer_trx_lines ctl
5515              WHERE    ctl.customer_trx_line_id = ctls.customer_trx_line_id
5516              AND      ctl.customer_trx_id      = p_customer_trx_id
5517              GROUP BY ctls.customer_trx_line_id,
5518                       ctl.extended_amount
5519              HAVING   (
5520                        -- Check Revenue Amount Split
5521                         ctl.extended_amount <> SUM(
5522                                              NVL(ctls.revenue_amount_split, 0)
5523                                                   )  AND
5524                         100 = SUM(
5525                                     NVL(ctls.revenue_percent_split, 0)
5526                                   )
5527                       )
5528                     OR
5529                       -- Check Revenue Percent Split
5530                       (
5531                          100   <> SUM(
5532                                        NVL(ctls.revenue_percent_split, 0)
5533                                      ) AND
5534                          ctl.extended_amount = SUM(
5535                                             NVL(ctls.revenue_amount_split, 0)
5536                                                   )
5537                       )
5538            );
5539 
5540    l_count := sql%rowcount;
5541 
5542   IF PG_DEBUG in ('Y', 'C') THEN
5543      arp_util.debug('Salescredit Revenue Errors Corrected    : ' || l_count);
5544   END IF;
5545 
5546    p_rows_processed := l_count;
5547 
5548    arp_util.print_fcn_label( 'arp_rounding.correct_scredit_rounding_errs()- ');
5549 
5550 EXCEPTION
5551    WHEN OTHERS THEN
5552 
5553     ROLLBACK TO SAVEPOINT ARPLBCRE_2;
5554 
5555     IF PG_DEBUG in ('Y', 'C') THEN
5556        arp_util.debug('EXCEPTION:  arp_rounding.correct_scredit_rounding_errs()');
5557        arp_util.debug('p_customer_trx_id = ' || p_customer_trx_id);
5558     END IF;
5559 
5560 
5561     RAISE;
5562 
5563 end correct_scredit_rounding_errs;
5564 
5565 BEGIN
5566    /* 7039838 - Detect if this is an autoinvoice session.  If so,
5567       set g_autoinv to TRUE, otherwise FALSE.  This will
5568       impact the content of several sqls in this package
5569       for performance tuning.  */
5570    BEGIN
5571       SELECT req.request_id
5572       INTO   g_autoinv_request_id
5573       FROM  fnd_concurrent_programs prog,
5574             fnd_concurrent_requests req
5575       WHERE req.request_id = FND_GLOBAL.CONC_REQUEST_ID
5576       AND   req.concurrent_program_id = prog.concurrent_program_id
5577       AND   prog.application_id = 222
5578       AND   prog.concurrent_program_name = 'RAXTRX';
5579 
5580       IF g_autoinv_request_id is not NULL
5581       THEN
5582          g_autoinv := TRUE;
5583       ELSE
5584          /* Dummy condition, never gets executed */
5585          g_autoinv := FALSE;
5586       END IF;
5587 
5588    EXCEPTION
5589       WHEN OTHERS THEN
5590          g_autoinv := FALSE;
5591    END;
5592 END ARP_ROUNDING;