DBA Data[Home] [Help]

PACKAGE BODY: APPS.ARP_ROUNDING

Source


1 PACKAGE BODY ARP_ROUNDING AS
2 /* $Header: ARPLCREB.pls 120.38.12010000.5 2008/12/01 06:30:03 ankuagar 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
334  |    This means that we will generally update REV lines for both invoices
331  |    date with an amount that has the same sign as the extended_amount
332  |    of the line.
333  |
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;
442         /* True the rows (if required) */
439 
440         CLOSE true_rows_by_date;
441      ELSE
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  |                                                                           |
555  | MODIFICATION HISTORY                                                      |
552  |                                                                           |
553  | NOTES                                                                     |
554  |                                                                           |
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  |                                                                         |
656  |   4) TRX_CLASS_TO_PROCESS must be either null, REGULAR_CM, INV or ALL.  |
653  |   3) If CUSTOMER_TRX_LINE_ID is specified, CUSTOMER_TRX_ID must be      |
654  |      specified.                                                         |
655  |                                                                         |
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
762        OR
759           p_customer_trx_id      IS NULL AND
760           p_customer_trx_line_id IS NULL
761         )
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()- ' ||
917   RETURN( iTRUE );
914                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
915   END IF;
916 
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                        ,
1025   ATTRIBUTE3                      ,
1022   ATTRIBUTE_CATEGORY              ,
1023   ATTRIBUTE1                      ,
1024   ATTRIBUTE2                      ,
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                )
1176 'ROUND',
1173 select
1174 POST_REQUEST_ID,
1175 -3,
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 *
1327                                 nvl(ct.exchange_rate,1)
1324                               nvl(ct.exchange_rate,1),
1325                                           fc.precision),
1326                         round( (l.extended_amount *
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,
1430                                 P_ERROR_MESSAGE        OUT NOCOPY VARCHAR2,
1427                                 P_CUSTOMER_TRX_ID       IN NUMBER,
1428                                 P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
1429                                 P_ROWS_PROCESSED    IN OUT NOCOPY NUMBER,
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,
1541                                       P_BASE_PRECISION        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,
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,
1664                            round( (sum(l.extended_amount) *
1661                      null, round(sum(l.extended_amount) *
1662                                  max(nvl(exchange_rate,1)),
1663                                  p_base_precision),
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      /* Not autoinvoice, probably Rev Rec or forms logic */
1740 update ra_cust_trx_line_gl_dist rec
1741 set (amount, acctd_amount, percent) =
1742     ( select nvl(rec.amount, 0) +
1743              (sum(l.extended_amount) - nvl(rec.amount, 0) ),
1744              nvl(rec.acctd_amount, 0) +
1745              ( decode(p_base_mau,
1746                      null, round(sum(l.extended_amount) *
1747                                  max(nvl(exchange_rate,1)),
1748                                  p_base_precision),
1749                            round( (sum(l.extended_amount) *
1750                                    max(nvl(exchange_rate,1))
1751                                   ) / p_base_mau
1752                                  ) * p_base_mau
1753                      )
1754               - nvl(rec.acctd_amount, 0)
1755              ),    /* acctd_amount */
1756             rec.percent + (100 - rec.percent) /* percent */
1757       from  ra_customer_trx t,
1758             ra_customer_trx_lines l
1759       where t.customer_trx_id = l.customer_trx_id
1760       and   l.customer_trx_id = rec.customer_trx_id
1761       group by l.customer_trx_id,
1762                t.trx_number,
1763                t.invoice_currency_code,
1764                t.exchange_date,
1765                t.exchange_rate_type,
1766                exchange_rate
1767  ),
1768 last_updated_by = arp_global.last_updated_by,   /*Bug 2089972 */
1769 last_update_date = sysdate
1770 where customer_trx_id in
1771     ( select l.customer_trx_id
1772       from   ra_customer_trx t,
1773              ra_customer_trx_lines l,
1774              ra_cust_trx_line_gl_dist d
1775       where  t.customer_trx_id = l.customer_trx_id
1776       and    l.customer_trx_id = d.customer_trx_id
1777       and    d.account_class   = 'REC'
1778       and    d.latest_rec_flag = 'Y'
1779    /*-------------------------------------------------
1780                     ---CUT HERE---                   */
1784       and    nvl(t.previous_customer_trx_id, -1) =
1781       and    d.customer_trx_id = p_customer_trx_id
1782    /*
1783     *------------------------------------------------*/
1785                 decode(p_trx_class_to_process,
1786                        'INV',        -1,
1787                        'REGULAR_CM', t.previous_customer_trx_id,
1788                                      nvl(t.previous_customer_trx_id, -1) )
1789       having (
1790                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
1791                100 <> nvl(d.percent, 0) OR
1792                decode(p_base_mau,
1793                       null, round(sum(l.extended_amount) *
1794                                   max(nvl(exchange_rate,1)),
1795                                   p_base_precision),
1796                             round( (sum(l.extended_amount) *
1797                                     max(nvl(exchange_rate,1))
1798                                    ) / p_base_mau
1799                                  ) * p_base_mau
1800                        )
1801                   <> nvl(d.acctd_amount, 0) OR
1802                d.acctd_amount is null OR
1803                d.amount is null
1804              )
1805       group by l.customer_trx_id,
1806                t.trx_number,
1807                d.amount,
1808                d.acctd_amount,
1809                d.percent,
1810                t.invoice_currency_code,
1811                t.exchange_date,
1812                t.exchange_rate_type,
1813                exchange_rate
1814  )
1815 and rec.account_class = 'REC'
1816 and rec.gl_posted_date is null;
1817 
1818      END IF; /* g_autoinv case */
1819   end if; /* customer_trx_id case */
1820 
1821   l_count := SQL%ROWCOUNT;
1822 
1823   IF PG_DEBUG in ('Y', 'C') THEN
1824      arp_standard.debug('Rows Processed: '||
1825            l_count);
1826   END IF;
1827 
1828   p_rows_processed := p_rows_processed + l_count;
1829 
1830   IF PG_DEBUG in ('Y', 'C') THEN
1831      arp_standard.debug( 'arp_rounding.correct_receivables_header()- ' ||
1832                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
1833   END IF;
1834 
1835   /* MRC Processing */
1836   IF PG_DEBUG in ('Y', 'C') THEN
1837      arp_standard.debug('  doing rounding for MRC if necessary');
1838   END IF;
1839   ar_mrc_engine2.mrc_correct_rounding(
1840                    'CORRECT_RECEIVABLES_HEADER',
1841                    P_REQUEST_ID,
1842                    P_CUSTOMER_TRX_ID,
1843                    P_CUSTOMER_TRX_LINE_ID,
1844                    P_TRX_CLASS_TO_PROCESS
1845                   );
1846 
1847   return(iTRUE);
1848 
1849 end correct_receivables_header;
1850 
1851 /*-------------------------------------------------------------------------+
1852  | PRIVATE FUNCTION                                                        |
1853  |   correct_receivables_records()                                         |
1854  |                                                                         |
1855  | DESCRIPTION                                                             |
1856  |   This function corrects rounding errors in the Receivable records.     |
1857  |   This is the only function that modifies account set records because   |
1858  |   only the Receivable account set record has an amount.                 |
1859  |   This function corrects errors 1 and 2 as specified in the high level  |
1860  |   design document.                                                      |
1861  |                                                                         |
1862  | REQUIRES                                                                |
1863  |   All IN parameters                                                     |
1864  |                                                                         |
1865  | RETURNS                                                                 |
1866  |   TRUE  if no errors occur                                              |
1867  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
1868  |                                                                         |
1869  | NOTES                                                                   |
1870  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
1871  |                                                                         |
1872  | EXAMPLE                                                                 |
1873  |                                                                         |
1874  | MODIFICATION HISTORY                                                    |
1875  |                                                                         |
1876  | Nilesh Acharya   24-July-98    Changes for triangulation                |
1877  |                                                                         |
1878  +-------------------------------------------------------------------------*/
1879 
1880 FUNCTION correct_receivables_records(
1881 		P_REQUEST_ID            IN NUMBER,
1882                 P_CUSTOMER_TRX_ID       IN NUMBER,
1883                 P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
1884                 P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
1885                 P_ERROR_MESSAGE         OUT NOCOPY VARCHAR2,
1886                 P_BASE_PRECISION        IN NUMBER,
1887                 P_BASE_MAU              IN NUMBER,
1888                 P_TRX_CLASS_TO_PROCESS  IN VARCHAR2)
1889 
1890          RETURN NUMBER IS
1891   l_count number;
1892 BEGIN
1893 
1894   IF PG_DEBUG in ('Y', 'C') THEN
1898 
1895      arp_standard.debug('arp_rounding.correct_receivables_record()+ ' ||
1896                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
1897   END IF;
1899   IF (p_request_id IS NOT NULL)
1900   THEN
1901 
1902 /******************************************************
1903  * Bug 13434104                                       *
1904  * Removed the call to gl_currency_api.convert_amount *
1905  ******************************************************/
1906 
1907 UPDATE ra_cust_trx_line_gl_dist rec
1908 SET (amount, acctd_amount, percent) =
1909     ( SELECT
1910              NVL(rec.amount, 0) +
1911              (SUM(l.extended_amount) - NVL(rec.amount, 0) ),
1912              NVL(rec.acctd_amount, 0) +
1913              (
1914               sum( decode(p_base_mau,
1915                           null, round(l.extended_amount *
1916                                  nvl(exchange_rate,1),
1917                                  p_base_precision),
1918                            round( (l.extended_amount *
1919                                    nvl(exchange_rate,1)
1920                                    ) / p_base_mau
1921                                  ) * p_base_mau
1922                            )
1923                   )
1924                  - NVL(rec.acctd_amount, 0)
1925              ),    /* acctd_amount */
1926             rec.percent + (100 - rec.percent) /* percent */
1927       FROM
1928             ra_customer_trx_lines l,
1929             ra_customer_trx t
1930       WHERE
1931             t.customer_trx_id = rec.customer_trx_id
1932       AND   l.customer_trx_id = t.customer_trx_id
1933       GROUP BY
1934             l.customer_trx_id,
1935             t.trx_number
1936     ),
1937 last_updated_by = arp_global.last_updated_by,       /* Bug 2089972 */
1938 last_update_date = sysdate
1939 WHERE customer_trx_id IN
1940     ( SELECT
1941              l.customer_trx_id
1942       FROM
1943              ra_customer_trx_lines l,
1944              ra_customer_trx t,
1945              ra_cust_trx_line_gl_dist d
1946       WHERE
1947              t.customer_trx_id = d.customer_trx_id
1948       AND    l.customer_trx_id = t.customer_trx_id
1949       AND    d.account_class   = 'REC'
1950       AND    d.latest_rec_flag = 'Y'
1951    /*-------------------------------------------
1952                  ---CUT HERE---                */
1953       AND    d.request_id      = p_request_id
1954    /*                                          *
1955     *------------------------------------------*/
1956       AND    NVL(t.previous_customer_trx_id, -1) =
1957                 DECODE(p_trx_class_to_process,
1958                        'INV',        -1,
1959                        'REGULAR_CM', t.previous_customer_trx_id,
1960                                      nvl(t.previous_customer_trx_id, -1) )
1961       having (
1962                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
1963                100 <> nvl(d.percent, 0) OR
1964               sum(
1965                                 decode(p_base_mau,
1966                                        null, round(l.extended_amount *
1967                                              nvl(exchange_rate,1),
1968                                              p_base_precision),
1969                                        round( (l.extended_amount *
1970                                                nvl(exchange_rate,1)
1971                                                ) / p_base_mau
1972                                              ) * p_base_mau
1973                                        )
1974                    )
1975                   <> nvl(d.acctd_amount, 0) OR
1976                d.acctd_amount is null OR
1977                d.amount is null
1978              )
1979       GROUP BY
1980                l.customer_trx_id,
1981                t.trx_number,
1982                d.amount,
1983                d.acctd_amount,
1984                d.percent
1985     )
1986 AND rec.account_class  = 'REC'
1987 AND rec.gl_posted_date IS NULL;
1988 
1989   END IF; /* request_id case */
1990 
1991   IF (p_customer_trx_id IS NOT NULL)
1992   THEN
1993 
1994 UPDATE ra_cust_trx_line_gl_dist rec
1995 SET (amount, acctd_amount, percent) =
1996     ( SELECT
1997              NVL(rec.amount, 0) +
1998              (SUM(l.extended_amount) - NVL(rec.amount, 0) ),
1999              NVL(rec.acctd_amount, 0) +
2000              (
2001               sum(
2002                                 decode(p_base_mau,
2003                                        null, round(l.extended_amount *
2004                                              nvl(exchange_rate,1),
2005                                              p_base_precision),
2006                                        round( (l.extended_amount *
2007                                                nvl(exchange_rate,1)
2008                                                ) / p_base_mau
2009                                              ) * p_base_mau
2010                                        )
2011                    )
2012                  - NVL(rec.acctd_amount, 0)
2013              ),
2014             rec.percent + (100 - rec.percent) /* percent */
2015       FROM
2016             ra_customer_trx_lines l,
2017             ra_customer_trx t
2018       WHERE
2019             t.customer_trx_id = rec.customer_trx_id
2020       AND   l.customer_trx_id = t.customer_trx_id
2021       GROUP BY
2022             l.customer_trx_id,
2023             t.trx_number
2024     ),
2028     ( SELECT
2025 last_updated_by = arp_global.last_updated_by,                /* Bug 2089972 */
2026 last_update_date = sysdate
2027 WHERE customer_trx_id IN
2029              l.customer_trx_id
2030       FROM
2031              ra_customer_trx t,
2032              ra_customer_trx_lines l,
2033              ra_cust_trx_line_gl_dist d
2034       WHERE
2035              t.customer_trx_id = d.customer_trx_id
2036       AND    l.customer_trx_id = t.customer_trx_id
2037       AND    d.account_class   = 'REC'
2038       AND    d.latest_rec_flag = 'Y'
2039    /*-------------------------------------------------
2040                     ---CUT HERE---                   */
2041       AND    d.customer_trx_id = p_customer_trx_id
2042    /*
2043     *------------------------------------------------*/
2044       AND    NVL(t.previous_customer_trx_id, -1) =
2045                 DECODE(p_trx_class_to_process,
2046                        'INV', -1,
2047                        'REGULAR_CM', t.previous_customer_trx_id,
2048                                      nvl(t.previous_customer_trx_id, -1) )
2049       having (
2050                sum(l.extended_amount) <> nvl(d.amount, 0)  OR
2051                100 <> nvl(d.percent, 0) OR
2052               sum(
2053                                 decode(p_base_mau,
2054                                        null, round(l.extended_amount *
2055                                              nvl(exchange_rate,1),
2056                                              p_base_precision),
2057                                        round( (l.extended_amount *
2058                                                nvl(exchange_rate,1)
2059                                                ) / p_base_mau
2060                                              ) * p_base_mau
2061                                        )
2062                    )
2063                   <> nvl(d.acctd_amount, 0) OR
2064                d.acctd_amount is null OR
2065                d.amount is null
2066              )
2067       GROUP BY
2068                l.customer_trx_id,
2069                t.trx_number,
2070                d.amount,
2071                d.acctd_amount,
2072                d.percent
2073     )
2074 AND rec.account_class  = 'REC'
2075 AND rec.gl_posted_date IS NULL;
2076 
2077   END IF; /* customer_trx_id case */
2078 
2079 
2080   l_count := sql%rowcount;
2081 
2082   IF PG_DEBUG in ('Y', 'C') THEN
2083      arp_standard.debug(
2084           'Rows Processed: '||
2085            l_count);
2086   END IF;
2087 
2088   p_rows_processed := p_rows_processed + l_count;
2089 
2090   IF PG_DEBUG in ('Y', 'C') THEN
2091      arp_standard.debug('arp_rounding.correct_receivables_record()- ' ||
2092                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
2093   END IF;
2094 
2095   /* MRC Processing */
2096   IF PG_DEBUG in ('Y', 'C') THEN
2097      arp_standard.debug('doing rounding for MRC if necessary');
2098   END IF;
2099   ar_mrc_engine2.mrc_correct_rounding(
2100                    'CORRECT_RECEIVABLES_RECORDS',
2101                    P_REQUEST_ID,
2102                    P_CUSTOMER_TRX_ID,
2103                    P_CUSTOMER_TRX_LINE_ID,
2104                    P_TRX_CLASS_TO_PROCESS
2105                   );
2106 
2107   RETURN( iTRUE );
2108 EXCEPTION
2109   WHEN others THEN
2110     p_error_message := SQLERRM;
2111     IF PG_DEBUG in ('Y', 'C') THEN
2112        arp_standard.debug('EXCEPTION:  arp_rounding.correct_receivables_record()- '||
2113                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
2114     END IF;
2115     RETURN(iFALSE);
2116 
2117 END correct_receivables_records;
2118 
2119 /*-------------------------------------------------------------------------+
2120  | PRIVATE FUNCTION                                                        |
2121  |   correct_nonrule_line_records()                                        |
2122  |                                                                         |
2123  | DESCRIPTION                                                             |
2124  |   This function corrects errors in the tax, freight, charges and        |
2125  |   AutoInvoice Clearing lines as well as in LINE lines that do not       |
2126  |   use rules.                                                            |
2127  |   This function corrects errors 3 - 8 as specified in the high level    |
2128  |   design document.                                                      |
2129  |                                                                         |
2130  | REQUIRES                                                                |
2131  |   All IN parameters                                                     |
2132  |                                                                         |
2133  | RETURNS                                                                 |
2134  |   TRUE  if no errors occur                                              |
2135  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
2136  |                                                                         |
2137  | NOTES                                                                   |
2138  |   *** PLEASE READ THE PACKAGE LEVEL NOTE BEFORE MODIFYING THIS FUNCTION.|
2139  |                                                                         |
2140  | EXAMPLE                                                                 |
2141  |                                                                         |
2142  | MODIFICATION HISTORY                                                    |
2146  |    07-OCT-02      M Raymond        Restructured nonrule sql to
2143  |                                                                         |
2144  |    15-NOV-98      Manoj Gudivaka   Fix for Bug 718096)                  |
2145  |    29-JUL-02      M Raymond        Added hints for bug 2398437
2147  |                                    resolve performance problem from
2148  |                                    bug 2539296.
2149  |    14-MAY-08      M Raymond       7039838 Performance tuning
2150  +-------------------------------------------------------------------------*/
2151  /*------------------------------------------------------------------------+
2152  | Modification for bug 718096                                             |
2153  |                                                                         |
2154  | Removed "account class" from the group by clause so that the rounding is|
2155  | done on the whole transaction amount rather than indiviually for the    |
2156  | Revenue amount and the Suspense Amount.                                 |
2157  |                                                                         |
2158  | The following Decode statement has been removed and replaced with       |
2159  | just the "extended amount"                                              |
2160  |                                                                         |
2161  |     DECODE(lgd2.account_class,                                          |
2162  |                         'REV', ctl.revenue_amount,                      |
2163  |                    'SUSPENSE', ctl.extended_amount - ctl.revenue_amount,|
2164  |                                ctl.extended_amount)                     |
2165  |                                                                         |
2166  +-------------------------------------------------------------------------*/
2167 
2168 FUNCTION correct_nonrule_line_records(
2169 		P_REQUEST_ID            IN NUMBER,
2170                 P_CUSTOMER_TRX_ID       IN NUMBER,
2171                 P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
2172                 P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
2173                 P_ERROR_MESSAGE         OUT NOCOPY VARCHAR2,
2174                 P_BASE_PRECISION        IN NUMBER,
2175                 P_BASE_MAU              IN NUMBER,
2176                 P_TRX_CLASS_TO_PROCESS  IN VARCHAR2)
2177 
2178          RETURN NUMBER IS
2179   l_count number;
2180 
2181 BEGIN
2182 
2183   IF PG_DEBUG in ('Y', 'C') THEN
2184      arp_standard.debug('arp_rounding.correct_nonrule_line_records()+ ' ||
2185                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
2186   END IF;
2187 
2188   IF (p_request_id IS NOT NULL)
2189   THEN
2190 
2191   /* Bug 2539296 - The sql below was slightly restructured for better
2192      performance in large databases.  I basically restructured the join
2193      order around ra_customer_trx instead of the gl_dist tables.
2194   */
2195 
2196 UPDATE ra_cust_trx_line_gl_dist lgd
2197 SET    (amount, acctd_amount)  =
2198        (SELECT NVL(lgd.amount, 0) -
2199                             (
2200                              SUM(lgd2.amount) -
2201                               (
2202                                  DECODE(lgd.gl_date,
2203                                         rec1.gl_date, 1,
2204                                         0) *
2205                                         ctl.extended_amount
2206                               )
2207                             ),  /* entered amount */
2208                NVL(lgd.acctd_amount, 0) -
2209                  (
2210                    SUM(lgd2.acctd_amount) -
2211                    (
2212                      DECODE(lgd.gl_date,
2213                             rec1.gl_date, 1,
2214                             0) *
2215                      DECODE(p_base_mau,
2216                                   NULL, ROUND( ctl.extended_amount *
2217                                                NVL(ct.exchange_rate,1),
2218                                                p_base_precision),
2219                                         ROUND( ( ctl.extended_amount *
2220                                                  NVL(ct.exchange_rate,1)
2221                                                ) / p_base_mau ) * p_base_mau
2222                            )
2223                    )
2224                  )              /* accounted amount */
2225                  FROM
2226                           ra_customer_trx_lines ctl,
2227                           ra_customer_trx ct,
2228                           ra_cust_trx_line_gl_dist lgd2,
2229                           ra_cust_trx_line_gl_dist rec1
2230                  WHERE
2231                           ctl.customer_trx_line_id = lgd2.customer_trx_line_id
2232                  AND      ctl.customer_trx_id      = ct.customer_trx_id
2233                  AND      lgd.customer_trx_line_id = ctl.customer_trx_line_id
2234 -- 718096          AND      lgd.account_class        = lgd2.account_class
2235                  AND      lgd2.account_set_flag    = 'N'
2236                  AND      rec1.customer_trx_id     = ct.customer_trx_id
2237                  AND      rec1.account_class       = 'REC'
2238                  AND      rec1.latest_rec_flag     = 'Y'
2239                  AND      NVL(lgd.gl_date, to_date( 2415021, 'J') )  =
2240                           NVL(lgd2.gl_date, to_date( 2415021, 'J') )
2241                  GROUP BY
2242                           ctl.customer_trx_line_id,
2243 -- 718096                   lgd2.account_class,
2244                           rec1.gl_date,
2245                           ctl.extended_amount,
2246                           ctl.revenue_amount,
2250        (SELECT    DECODE(lgd.account_class || lgd.account_set_flag,
2247                           ct.exchange_rate
2248        ),
2249        percent =
2251                          'SUSPENSEN', lgd.percent,
2252                          'UNBILLN', lgd.percent,
2253                          'UNEARNN', lgd.percent,
2254                          NVL(lgd.percent, 0) -
2255                                (
2256                                  SUM(NVL(lgd4.percent, 0))
2257                                      - DECODE(rec2.gl_date,
2258                                               NVL(lgd.gl_date,
2259                                                   rec2.gl_date), 100,
2260                                               0)
2261                                )
2262                         )  /* percent */
2263         FROM
2264                   ra_cust_trx_line_gl_dist lgd4,
2265                   ra_cust_trx_line_gl_dist rec2
2266         WHERE
2267                   lgd.customer_trx_line_id = lgd4.customer_trx_line_id
2268         AND       rec2.customer_trx_id     = lgd.customer_trx_id
2269         AND       rec2.account_class       = 'REC'
2270         AND       rec2.latest_rec_flag     = 'Y'
2271         AND       lgd4.account_set_flag    = lgd.account_set_flag
2272         AND       DECODE(lgd4.account_set_flag,
2273                          'Y', lgd4.account_class,
2274                          lgd.account_class) = lgd.account_class
2275         AND       NVL(lgd.gl_date, to_date( 2415021, 'J') )  =
2276                   NVL(lgd4.gl_date, to_date( 2415021, 'J') )
2277         GROUP BY
2278                   rec2.gl_date,
2279                   lgd.gl_date
2280        ),
2281 last_updated_by = arp_global.last_updated_by,   /* Bug 2089972 */
2282 last_update_date = sysdate
2283  WHERE cust_trx_line_gl_dist_id  IN
2284        (SELECT /*+ INDEX (lgd3 ra_cust_trx_line_gl_dist_n7) */
2285                MIN(DECODE(lgd3.gl_posted_date,
2286                           NULL, lgd3.cust_trx_line_gl_dist_id,
2287                           NULL) )
2288         FROM
2289                ra_customer_trx_lines ctl,
2290                ra_customer_trx t,
2291                ra_cust_trx_line_gl_dist lgd3,
2292                ra_cust_trx_line_gl_dist rec3
2293         WHERE
2294                t.request_id         = p_request_id
2295         AND    T.CUSTOMER_TRX_ID    = CTL.CUSTOMER_TRX_ID
2296         AND   (CTL.LINE_TYPE IN ( 'TAX','FREIGHT','CHARGES','SUSPENSE'  ) OR
2297               (CTL.LINE_TYPE = 'LINE'  AND CTL.ACCOUNTING_RULE_ID IS NULL ))
2298         AND    LGD3.CUSTOMER_TRX_LINE_ID = CTL.CUSTOMER_TRX_LINE_ID
2299         AND    LGD3.ACCOUNT_SET_FLAG = 'N'
2300         AND    REC3.CUSTOMER_TRX_ID = T.CUSTOMER_TRX_ID
2301         AND    REC3.ACCOUNT_CLASS = 'REC'
2302         AND    REC3.LATEST_REC_FLAG = 'Y'
2303         AND    NVL(t.previous_customer_trx_id, -1) =
2304                 DECODE(p_trx_class_to_process,
2305                        'INV', -1,
2306                        'REGULAR_CM', t.previous_customer_trx_id,
2307                        NVL(t.previous_customer_trx_id, -1) )
2308         GROUP BY
2309                  ctl.customer_trx_line_id,
2310 --  718096         lgd3.account_class,
2311                  lgd3.gl_date,
2312                  rec3.gl_date,
2313                  ctl.extended_amount,
2314                  ctl.revenue_amount,
2315                  t.exchange_rate
2316         HAVING (
2317                   SUM(NVL(lgd3.amount, 0))
2318                                   <> ctl.extended_amount *
2319                                      DECODE(lgd3.gl_date,
2320                                             rec3.gl_date, 1,
2321                                             0)
2322                 OR
2323                   SUM(NVL(lgd3.acctd_amount, 0)) <>
2324                   DECODE(lgd3.gl_date,
2325                          rec3.gl_date, 1,
2326                          0) *
2327                   DECODE(p_base_mau,
2328                          NULL, ROUND( ctl.extended_amount *
2329                                       NVL(t.exchange_rate,1),
2330                                       p_base_precision ),
2331                                ROUND( ( ctl.extended_amount *
2332                                        NVL(t.exchange_rate,1)
2333                                       ) / p_base_mau ) * p_base_mau
2334                         )
2335                )
2336        UNION
2337        SELECT /*+ INDEX (lgd5 ra_cust_trx_line_gl_dist_n7) */
2338              TO_NUMBER(
2339                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
2340                                     lgd5.account_set_flag,
2341                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
2342                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
2343                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
2344                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
2345                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
2346                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
2347                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
2348                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
2349                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
2350                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
2351                                      NULL ) )
2352                       )
2353        FROM
2354               ra_cust_trx_line_gl_dist lgd5,
2355               ra_cust_trx_line_gl_dist rec5,
2356               ra_customer_trx_lines ctl2,
2360        AND    T.CUSTOMER_TRX_ID = REC5.CUSTOMER_TRX_ID
2357               ra_customer_trx t
2358        WHERE
2359               T.REQUEST_ID = p_request_id
2361        AND    CTL2.CUSTOMER_TRX_LINE_ID = LGD5.CUSTOMER_TRX_LINE_ID
2362        AND    REC5.CUSTOMER_TRX_ID = LGD5.CUSTOMER_TRX_ID
2363        AND    REC5.ACCOUNT_CLASS = 'REC'
2364        AND    REC5.LATEST_REC_FLAG = 'Y'
2365        AND   (CTL2.LINE_TYPE IN ( 'TAX','FREIGHT','CHARGES','SUSPENSE')
2366                 OR
2367              (CTL2.LINE_TYPE = 'LINE'  AND
2368              (CTL2.ACCOUNTING_RULE_ID IS NULL  OR LGD5.ACCOUNT_SET_FLAG = 'Y' )))
2369        GROUP BY
2370                 lgd5.customer_trx_line_id,
2371                 lgd5.gl_date,
2372                 rec5.gl_date,
2373                 lgd5.account_set_flag,
2374                 DECODE(lgd5.account_set_flag,
2375                        'N', NULL,
2376                        lgd5.account_class)
2377        HAVING
2378               SUM(NVL(lgd5.percent, 0)) <>
2379                  DECODE( NVL(lgd5.gl_date, rec5.gl_date),
2380                          rec5.gl_date, 100,
2381                          0)
2382      );
2383 
2384    END IF;  /* request_id case */
2385 
2386    IF (p_customer_trx_id IS NOT NULL AND p_customer_trx_line_id IS NULL)
2387    THEN
2388 
2389       IF g_autoinv
2390       THEN
2391          /* version tuned for autoinvoice with request_id joins */
2392 UPDATE ra_cust_trx_line_gl_dist lgd
2393 SET    (amount, acctd_amount)  =
2394        (SELECT /*+ index(LGD2 RA_CUST_TRX_LINE_GL_DIST_N10) */
2395                    NVL(lgd.amount, 0) -
2396                             (
2397                              SUM(lgd2.amount) -
2398                              (
2399                                  DECODE(lgd.gl_date,
2400                                         rec1.gl_date, 1,
2401                                         0) *
2402                                  DECODE(DECODE(lgd2.account_class,
2403                                                'UNEARN','REV',
2404                                                lgd2.account_class),
2405                                         'REV',       ctl.revenue_amount,
2406                                         'SUSPENSE',  ctl.extended_amount -
2407                                                      ctl.revenue_amount,
2408                                         ctl.extended_amount)
2409                              )
2410                             ),  /* entered amount */
2411                NVL(lgd.acctd_amount, 0) -
2412                  (
2413                    SUM(lgd2.acctd_amount) -
2414                    (
2415                      DECODE(lgd.gl_date,
2416                             rec1.gl_date, 1,
2417                             0) *
2418                      DECODE(p_base_mau,
2419                          NULL, ROUND(DECODE(DECODE(lgd2.account_class,
2420                                                    'UNEARN','REV',
2421                                                    lgd2.account_class),
2422                                             'REV',       ctl.revenue_amount,
2423                                             'SUSPENSE',  ctl.extended_amount -
2424                                                          ctl.revenue_amount,
2425                                             ctl.extended_amount) *
2426                                      NVL(ct.exchange_rate,1),
2427                                      p_base_precision ),
2428                                ROUND( (DECODE(DECODE(lgd2.account_class,
2429                                                      'UNEARN','REV',
2430                                                      lgd2.account_class),
2431                                             'REV',       ctl.revenue_amount,
2432                                             'SUSPENSE',  ctl.extended_amount -
2433                                                          ctl.revenue_amount,
2434                                             ctl.extended_amount) *
2435                                        NVL(ct.exchange_rate,1)
2436                                       ) / p_base_mau
2437                                     ) * p_base_mau
2438                         )
2439                    )
2440                  )              /* accounted amount */
2441                  FROM
2442                           ra_cust_trx_line_gl_dist lgd2,
2443                           ra_customer_trx_lines ctl,
2444                           ra_customer_trx ct,
2445                           ra_cust_trx_line_gl_dist rec1
2446                  WHERE
2447                           rec1.customer_trx_id      = lgd.customer_trx_id
2448                  AND      rec1.account_class        = 'REC'
2449                  AND      rec1.latest_rec_flag      = 'Y'
2450                  AND      ct.customer_trx_id        = rec1.customer_trx_id
2451                  AND      ctl.customer_trx_id       = ct.customer_trx_id
2452                  AND      ctl.customer_trx_line_id  = lgd.customer_trx_line_id
2453                  AND      lgd2.customer_trx_line_id = lgd.customer_trx_line_id
2454                  AND      lgd2.account_class        = lgd.account_class
2455                  AND      lgd2.account_set_flag     = 'N'
2456                  AND      lgd2.request_id = g_autoinv_request_id
2457                  AND      NVL(lgd2.gl_date, to_date( 2415021, 'J') )  =
2458                              NVL(lgd.gl_date, to_date( 2415021, 'J') )
2459                  GROUP BY
2460                           ctl.customer_trx_line_id,
2461                           DECODE(lgd2.account_class,'UNEARN','REV',
2462                                  lgd2.account_class),
2463                           rec1.gl_date,
2467        ),
2464                           ctl.extended_amount,
2465                           ctl.revenue_amount,
2466                           ct.exchange_rate
2468        percent =
2469        (SELECT /*+ index(LGD4 RA_CUST_TRX_LINE_GL_DIST_N10) */
2470                   DECODE(lgd.account_class || lgd.account_set_flag,
2471                          'SUSPENSEN', lgd.percent,
2472                          'UNBILLN', lgd.percent,
2473                          'UNEARNN', lgd.percent,
2474                          NVL(lgd.percent, 0) -
2475                                (
2476                                  SUM(NVL(lgd4.percent, 0))
2477                                  - DECODE(rec2.gl_date,
2478                                           NVL(lgd.gl_date, rec2.gl_date),
2479                                           100, 0)
2480                                )
2481                         )  /* percent */
2482         FROM
2483                   ra_cust_trx_line_gl_dist lgd4,
2484                   ra_cust_trx_line_gl_dist rec2
2485         WHERE
2486                   rec2.customer_trx_id      = lgd.customer_trx_id
2487         AND       rec2.account_class        = 'REC'
2488         AND       rec2.latest_rec_flag      = 'Y'
2489         AND       lgd4.customer_trx_line_id = lgd.customer_trx_line_id
2490         AND       lgd4.account_set_flag     = lgd.account_set_flag
2491         AND       DECODE(lgd4.account_set_flag,
2492                          'Y', lgd4.account_class,
2493                          lgd.account_class) = lgd.account_class
2494         AND       NVL(lgd4.gl_date, to_date( 2415021, 'J') )  =
2495                      NVL(lgd.gl_date, to_date( 2415021, 'J') )
2496         AND       lgd4.request_id = g_autoinv_request_id
2497         GROUP BY
2498                   rec2.gl_date,
2499                   lgd.gl_date
2500        ),
2501 last_updated_by = arp_global.last_updated_by,       /* Bug 2089972 */
2502 last_update_date = sysdate
2503 WHERE cust_trx_line_gl_dist_id  IN
2504        (SELECT /*+ leading(T,LGD3,REC3,CTL)
2505 	           use_hash(CTL) index(CTL RA_CUSTOMER_TRX_LINES_N4)
2506 	           index(LGD3 RA_CUST_TRX_LINE_GL_DIST_N6)
2507 	           index(REC3 RA_CUST_TRX_LINE_GL_DIST_N6) */
2508                MIN(DECODE(lgd3.gl_posted_date,
2509                           NULL, lgd3.cust_trx_line_gl_dist_id,
2510                           NULL) )
2511         FROM
2512                ra_customer_trx_lines ctl,
2513                ra_cust_trx_line_gl_dist lgd3,
2514                ra_cust_trx_line_gl_dist rec3,
2515                ra_customer_trx t
2516         WHERE
2517                t.customer_trx_id        = p_customer_trx_id
2518         AND    rec3.customer_trx_id     = t.customer_trx_id
2519         AND    rec3.account_class       = 'REC'
2520         AND    rec3.latest_rec_flag     = 'Y'
2521         AND    lgd3.customer_trx_id     = t.customer_trx_id
2522         AND    lgd3.account_set_flag    = 'N'
2523         AND    ctl.customer_trx_line_id = lgd3.customer_trx_line_id
2524         AND    (
2525                   ctl.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2526                 OR
2527                   (ctl.line_type = 'LINE' AND ctl.accounting_rule_id IS NULL)
2528                )
2529         AND    ctl.request_id = g_autoinv_request_id
2530         AND    ctl.customer_trx_id = p_customer_trx_id
2531         AND    NVL(t.previous_customer_trx_id, -1) =
2532                 DECODE(p_trx_class_to_process,
2533                        'INV', -1,
2534                        'REGULAR_CM', t.previous_customer_trx_id,
2535                        NVL(t.previous_customer_trx_id, -1) )
2536         GROUP BY
2537                  ctl.customer_trx_line_id,
2538                  DECODE(lgd3.account_class,'UNEARN','REV',lgd3.account_class),
2539                  lgd3.gl_date,
2540                  rec3.gl_date,
2541                  ctl.extended_amount,
2542                  ctl.revenue_amount,
2543                  t.exchange_rate
2544         HAVING (
2545                   SUM(NVL(lgd3.amount, 0))
2546                             <> DECODE(DECODE(lgd3.account_class,
2547                                              'UNEARN','REV',lgd3.account_class),
2548                                      'REV',       ctl.revenue_amount,
2549                                      'SUSPENSE',  ctl.extended_amount -
2550                                                          ctl.revenue_amount,
2551                                       ctl.extended_amount) *
2552                                DECODE(lgd3.gl_date,
2553                                       rec3.gl_date, 1,
2554                                       0)
2555                 OR
2556                   SUM(NVL(lgd3.acctd_amount, 0)) <>
2557                   DECODE(lgd3.gl_date,
2558                          rec3.gl_date, 1,
2559                          0) *
2560                   DECODE(p_base_mau,
2561                          NULL, ROUND(DECODE(DECODE(lgd3.account_class,
2562                                                    'UNEARN','REV',
2563                                                    lgd3.account_class),
2564                                             'REV',       ctl.revenue_amount,
2565                                             'SUSPENSE',  ctl.extended_amount -
2566                                                          ctl.revenue_amount,
2567                                             ctl.extended_amount) *
2568                                      NVL(t.exchange_rate,1),
2569                                      p_base_precision),
2570                          ROUND( (DECODE(DECODE(lgd3.account_class,
2574                                             'SUSPENSE',  ctl.extended_amount -
2571                                                'UNEARN','REV',
2572                                                lgd3.account_class),
2573                                             'REV',       ctl.revenue_amount,
2575                                                          ctl.revenue_amount,
2576                                             ctl.extended_amount) *
2577                                        NVL(t.exchange_rate,1)
2578                                 ) / p_base_mau
2579                               ) * p_base_mau
2580                         )
2581                )
2582        UNION
2583        SELECT  /*+ leading(CTL2 LGD5,REC5)
2584 	           use_hash(LGD5) index(CTL2 RA_CUSTOMER_TRX_LINES_N4)
2585 		   index(REC5 RA_CUST_TRX_LINE_GL_DIST_N6)
2586 		   index(LGD5 RA_CUST_TRX_LINE_GL_DIST_N6) */
2587                TO_NUMBER(
2588                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
2589                                     lgd5.account_set_flag,
2590                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
2591                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
2592                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
2593                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
2594                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
2595                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
2596                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
2597                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
2598                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
2599                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
2600                                      NULL
2601                                    )
2602                             )
2603                        )
2604        FROM
2605               ra_cust_trx_line_gl_dist rec5,
2606               ra_cust_trx_line_gl_dist lgd5,
2607               ra_customer_trx_lines ctl2
2608        WHERE
2609               ctl2.customer_trx_id      = p_customer_trx_id
2610        AND    ctl2.request_id           = g_autoinv_request_id
2611        AND    rec5.customer_trx_id      = lgd5.customer_trx_id
2612        AND    rec5.account_class        = 'REC'
2613        AND    rec5.latest_rec_flag      = 'Y'
2614        AND    lgd5.customer_trx_line_id = ctl2.customer_trx_line_id
2615        AND    lgd5.customer_trx_id      = p_customer_trx_id
2616        AND    (
2617                 ctl2.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2618                 OR
2619                 (ctl2.line_type = 'LINE'   AND
2620                  (ctl2.accounting_rule_id  IS NULL OR
2621                      lgd5.account_set_flag = 'Y')
2622                 )
2623               )
2624        GROUP BY
2625                 lgd5.customer_trx_line_id,
2626                 lgd5.gl_date,
2627                 rec5.gl_date,
2628                 lgd5.account_set_flag,
2629                 DECODE(lgd5.account_set_flag,
2630                        'N', NULL,
2631                        lgd5.account_class)
2632        HAVING SUM(NVL(lgd5.percent, 0)) <>
2633               DECODE( NVL(lgd5.gl_date, rec5.gl_date),
2634                       rec5.gl_date, 100,
2635                       0)
2636        );
2637 
2638       ELSE
2639          /* original version (used by forms and Rev Rec */
2640 UPDATE ra_cust_trx_line_gl_dist lgd
2641 SET    (amount, acctd_amount)  =
2642        (SELECT NVL(lgd.amount, 0) -
2643                             (
2644                              SUM(lgd2.amount) -
2645                              (
2646                                  DECODE(lgd.gl_date,
2647                                         rec1.gl_date, 1,
2648                                         0) *
2649                                  DECODE(DECODE(lgd2.account_class,
2650                                                'UNEARN','REV',
2651                                                lgd2.account_class),
2652                                         'REV',       ctl.revenue_amount,
2653                                         'SUSPENSE',  ctl.extended_amount -
2654                                                      ctl.revenue_amount,
2655                                         ctl.extended_amount)
2656                              )
2657                             ),  /* entered amount */
2658                NVL(lgd.acctd_amount, 0) -
2659                  (
2660                    SUM(lgd2.acctd_amount) -
2661                    (
2662                      DECODE(lgd.gl_date,
2663                             rec1.gl_date, 1,
2664                             0) *
2665                      DECODE(p_base_mau,
2666                          NULL, ROUND(DECODE(DECODE(lgd2.account_class,
2667                                                    'UNEARN','REV',
2668                                                    lgd2.account_class),
2669                                             'REV',       ctl.revenue_amount,
2670                                             'SUSPENSE',  ctl.extended_amount -
2671                                                          ctl.revenue_amount,
2672                                             ctl.extended_amount) *
2673                                      NVL(ct.exchange_rate,1),
2674                                      p_base_precision ),
2675                                ROUND( (DECODE(DECODE(lgd2.account_class,
2679                                             'SUSPENSE',  ctl.extended_amount -
2676                                                      'UNEARN','REV',
2677                                                      lgd2.account_class),
2678                                             'REV',       ctl.revenue_amount,
2680                                                          ctl.revenue_amount,
2681                                             ctl.extended_amount) *
2682                                        NVL(ct.exchange_rate,1)
2683                                       ) / p_base_mau
2684                                     ) * p_base_mau
2685                         )
2686                    )
2687                  )              /* accounted amount */
2688                  FROM
2689                           ra_cust_trx_line_gl_dist lgd2,
2690                           ra_customer_trx_lines ctl,
2691                           ra_customer_trx ct,
2692                           ra_cust_trx_line_gl_dist rec1
2693                  WHERE
2694                           rec1.customer_trx_id      = lgd.customer_trx_id
2695                  AND      rec1.account_class        = 'REC'
2696                  AND      rec1.latest_rec_flag      = 'Y'
2697                  AND      ct.customer_trx_id        = rec1.customer_trx_id
2698                  AND      ctl.customer_trx_id       = ct.customer_trx_id
2699                  AND      ctl.customer_trx_line_id  = lgd.customer_trx_line_id
2700                  AND      lgd2.customer_trx_line_id = lgd.customer_trx_line_id
2701                  AND      lgd2.account_class        = lgd.account_class
2702                  AND      lgd2.account_set_flag     = 'N'
2703                  AND      NVL(lgd2.gl_date, to_date( 2415021, 'J') )  =
2704                              NVL(lgd.gl_date, to_date( 2415021, 'J') )
2705                  GROUP BY
2706                           ctl.customer_trx_line_id,
2707                           DECODE(lgd2.account_class,'UNEARN','REV',
2708                                  lgd2.account_class),
2709                           rec1.gl_date,
2710                           ctl.extended_amount,
2711                           ctl.revenue_amount,
2712                           ct.exchange_rate
2713        ),
2714        percent =
2715        (SELECT    DECODE(lgd.account_class || lgd.account_set_flag,
2716                          'SUSPENSEN', lgd.percent,
2717                          'UNBILLN', lgd.percent,
2718                          'UNEARNN', lgd.percent,
2719                          NVL(lgd.percent, 0) -
2720                                (
2721                                  SUM(NVL(lgd4.percent, 0))
2722                                  - DECODE(rec2.gl_date,
2723                                           NVL(lgd.gl_date, rec2.gl_date),
2724                                           100, 0)
2725                                )
2726                         )  /* percent */
2727         FROM
2728                   ra_cust_trx_line_gl_dist lgd4,
2729                   ra_cust_trx_line_gl_dist rec2
2730         WHERE
2731                   rec2.customer_trx_id      = lgd.customer_trx_id
2732         AND       rec2.account_class        = 'REC'
2733         AND       rec2.latest_rec_flag      = 'Y'
2734         AND       lgd4.customer_trx_line_id = lgd.customer_trx_line_id
2735         AND       lgd4.account_set_flag     = lgd.account_set_flag
2736         AND       DECODE(lgd4.account_set_flag,
2737                          'Y', lgd4.account_class,
2738                          lgd.account_class) = lgd.account_class
2739         AND       NVL(lgd4.gl_date, to_date( 2415021, 'J') )  =
2740                      NVL(lgd.gl_date, to_date( 2415021, 'J') )
2741         GROUP BY
2742                   rec2.gl_date,
2743                   lgd.gl_date
2744        ),
2745 last_updated_by = arp_global.last_updated_by,       /* Bug 2089972 */
2746 last_update_date = sysdate
2747 WHERE cust_trx_line_gl_dist_id  IN
2748        (SELECT MIN(DECODE(lgd3.gl_posted_date,
2749                           NULL, lgd3.cust_trx_line_gl_dist_id,
2750                           NULL) )
2751         FROM
2752                ra_customer_trx_lines ctl,
2753                ra_cust_trx_line_gl_dist lgd3,
2754                ra_cust_trx_line_gl_dist rec3,
2755                ra_customer_trx t
2756         WHERE
2757                t.customer_trx_id        = p_customer_trx_id
2758         AND    rec3.customer_trx_id     = t.customer_trx_id
2759         AND    rec3.account_class       = 'REC'
2760         AND    rec3.latest_rec_flag     = 'Y'
2761         AND    lgd3.customer_trx_id     = t.customer_trx_id
2762         AND    lgd3.account_set_flag    = 'N'
2763         AND    ctl.customer_trx_line_id = lgd3.customer_trx_line_id
2764         AND    (
2765                   ctl.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2766                 OR
2767                   (ctl.line_type = 'LINE' AND ctl.accounting_rule_id IS NULL)
2768                )
2769         AND    NVL(t.previous_customer_trx_id, -1) =
2770                 DECODE(p_trx_class_to_process,
2771                        'INV', -1,
2772                        'REGULAR_CM', t.previous_customer_trx_id,
2773                        NVL(t.previous_customer_trx_id, -1) )
2774         GROUP BY
2775                  ctl.customer_trx_line_id,
2776                  DECODE(lgd3.account_class,'UNEARN','REV',lgd3.account_class),
2777                  lgd3.gl_date,
2778                  rec3.gl_date,
2779                  ctl.extended_amount,
2780                  ctl.revenue_amount,
2781                  t.exchange_rate
2782         HAVING (
2786                                      'REV',       ctl.revenue_amount,
2783                   SUM(NVL(lgd3.amount, 0))
2784                             <> DECODE(DECODE(lgd3.account_class,
2785                                              'UNEARN','REV',lgd3.account_class),
2787                                      'SUSPENSE',  ctl.extended_amount -
2788                                                          ctl.revenue_amount,
2789                                       ctl.extended_amount) *
2790                                DECODE(lgd3.gl_date,
2791                                       rec3.gl_date, 1,
2792                                       0)
2793                 OR
2794                   SUM(NVL(lgd3.acctd_amount, 0)) <>
2795                   DECODE(lgd3.gl_date,
2796                          rec3.gl_date, 1,
2797                          0) *
2798                   DECODE(p_base_mau,
2799                          NULL, ROUND(DECODE(DECODE(lgd3.account_class,
2800                                                    'UNEARN','REV',
2801                                                    lgd3.account_class),
2802                                             'REV',       ctl.revenue_amount,
2803                                             'SUSPENSE',  ctl.extended_amount -
2804                                                          ctl.revenue_amount,
2805                                             ctl.extended_amount) *
2806                                      NVL(t.exchange_rate,1),
2807                                      p_base_precision),
2808                          ROUND( (DECODE(DECODE(lgd3.account_class,
2809                                                'UNEARN','REV',
2810                                                lgd3.account_class),
2811                                             'REV',       ctl.revenue_amount,
2812                                             'SUSPENSE',  ctl.extended_amount -
2813                                                          ctl.revenue_amount,
2814                                             ctl.extended_amount) *
2815                                        NVL(t.exchange_rate,1)
2816                                 ) / p_base_mau
2817                               ) * p_base_mau
2818                         )
2819                )
2820        UNION
2821        SELECT TO_NUMBER(
2822                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
2823                                     lgd5.account_set_flag,
2824                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
2825                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
2826                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
2827                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
2828                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
2829                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
2830                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
2831                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
2832                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
2833                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
2834                                      NULL
2835                                    )
2836                             )
2837                        )
2838        FROM
2839               ra_cust_trx_line_gl_dist rec5,
2840               ra_cust_trx_line_gl_dist lgd5,
2841               ra_customer_trx_lines ctl2
2842        WHERE
2843               ctl2.customer_trx_id      = p_customer_trx_id
2844        AND    rec5.customer_trx_id      = lgd5.customer_trx_id
2845        AND    rec5.account_class        = 'REC'
2846        AND    rec5.latest_rec_flag      = 'Y'
2847        AND    lgd5.customer_trx_line_id = ctl2.customer_trx_line_id
2848        AND    (
2849                 ctl2.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
2850                 OR
2851                 (ctl2.line_type = 'LINE'   AND
2852                  (ctl2.accounting_rule_id  IS NULL OR
2853                      lgd5.account_set_flag = 'Y')
2854                 )
2855               )
2856        GROUP BY
2857                 lgd5.customer_trx_line_id,
2858                 lgd5.gl_date,
2859                 rec5.gl_date,
2860                 lgd5.account_set_flag,
2861                 DECODE(lgd5.account_set_flag,
2862                        'N', NULL,
2863                        lgd5.account_class)
2864        HAVING SUM(NVL(lgd5.percent, 0)) <>
2865               DECODE( NVL(lgd5.gl_date, rec5.gl_date),
2866                       rec5.gl_date, 100,
2867                       0)
2868        );
2869 
2870       END IF; /* g_autoinv case */
2871    END IF; /* customer_trx_id case */
2872 
2873    IF (p_customer_trx_line_id IS NOT NULL)
2874    THEN
2875 
2876 UPDATE ra_cust_trx_line_gl_dist lgd
2877 SET    (amount, acctd_amount)  =
2878        (SELECT NVL(lgd.amount, 0) -
2879                             (
2880                              SUM(lgd2.amount) -
2881                              (
2882                                  DECODE(lgd.gl_date,
2883                                         rec1.gl_date, 1,
2884                                         0) *
2885                                  DECODE(DECODE(lgd2.account_class,
2886                                                'UNEARN','REV',
2887                                                lgd2.account_class),
2888                                         'REV',       ctl.revenue_amount,
2892                              )
2889                                         'SUSPENSE',  ctl.extended_amount -
2890                                                      ctl.revenue_amount,
2891                                         ctl.extended_amount)
2893                             ),  /* entered amount */
2894                NVL(lgd.acctd_amount, 0) -
2895                  (
2896                    SUM(lgd2.acctd_amount) -
2897                    (
2898                      DECODE(lgd.gl_date,
2899                             rec1.gl_date, 1,
2900                             0) *
2901                      DECODE(p_base_mau,
2902                          NULL, ROUND(DECODE(DECODE(lgd2.account_class,
2903                                                    'UNEARN','REV',
2904                                                    lgd2.account_class),
2905                                             'REV',       ctl.revenue_amount,
2906                                             'SUSPENSE',  ctl.extended_amount -
2907                                                          ctl.revenue_amount,
2908                                             ctl.extended_amount) *
2909                                      NVL(ct.exchange_rate,1),
2910                                      p_base_precision ),
2911                                ROUND( (DECODE(DECODE(lgd2.account_class,
2912                                                      'UNEARN','REV',
2913                                                      lgd2.account_class),
2914                                              'REV',       ctl.revenue_amount,
2915                                              'SUSPENSE',  ctl.extended_amount -
2916                                                           ctl.revenue_amount,
2917                                              ctl.extended_amount) *
2918                                        NVL(ct.exchange_rate,1)
2919                                       ) / p_base_mau
2920                                     ) * p_base_mau
2921                         )
2922                    )
2923                  )              /* accounted amount */
2924                  FROM
2925                           ra_cust_trx_line_gl_dist lgd2,
2926                           ra_customer_trx_lines ctl,
2927                           ra_customer_trx ct,
2928                           ra_cust_trx_line_gl_dist rec1
2929                  WHERE
2930                           rec1.customer_trx_id      = lgd.customer_trx_id
2931                  and      rec1.account_class        = 'REC'
2932                  and      rec1.latest_rec_flag      = 'Y'
2933                  and      ct.customer_trx_id        = rec1.customer_trx_id
2934                  and      ctl.customer_trx_id       = ct.customer_trx_id
2935                  and      ctl.customer_trx_line_id  = lgd.customer_trx_line_id
2936                  and      lgd2.customer_trx_line_id = lgd.customer_trx_line_id
2937                  and      lgd2.account_class        = lgd.account_class
2938                  and      lgd2.account_set_flag     = 'N'
2939                  and      NVL(lgd2.gl_date, to_date( 2415021, 'J') )  =
2940                              NVL(lgd.gl_date, to_date( 2415021, 'J') )
2941                  GROUP BY
2942                           ctl.customer_trx_line_id,
2943                           DECODE(lgd2.account_class,'UNEARN','REV',
2944                                  lgd2.account_class),
2945                           rec1.gl_date,
2946                           ctl.extended_amount,
2947                           ctl.revenue_amount,
2948                           ct.exchange_rate
2949        ),
2950        percent =
2951        (SELECT    DECODE(lgd.account_class || lgd.account_set_flag,
2952                          'SUSPENSEN', lgd.percent,
2953                          'UNBILLN', lgd.percent,
2954                          'UNEARNN', lgd.percent,
2955                          NVL(lgd.percent, 0) -
2956                                (
2957                                  SUM(NVL(lgd4.percent, 0))
2958                                  - DECODE(rec2.gl_date,
2959                                           NVL(lgd.gl_date, rec2.gl_date),
2960                                           100, 0)
2961                                )
2962                         )  /* percent */
2963         FROM
2964                   ra_cust_trx_line_gl_dist lgd4,
2965                   ra_cust_trx_line_gl_dist rec2
2966         WHERE
2967                   rec2.customer_trx_id      = lgd.customer_trx_id
2968         AND       rec2.account_class        = 'REC'
2969         AND       rec2.latest_rec_flag      = 'Y'
2970         AND       lgd4.customer_trx_line_id = lgd.customer_trx_line_id
2971         AND       lgd4.account_set_flag     = lgd.account_set_flag
2972         AND       DECODE(lgd4.account_set_flag,
2973                          'Y', lgd4.account_class,
2974                          lgd.account_class) = lgd.account_class
2975         AND       NVL(lgd4.gl_date, to_date( 2415021, 'J') )  =
2976                      NVL(lgd.gl_date, to_date( 2415021, 'J') )
2977         GROUP BY
2978                   rec2.gl_date,
2979                   lgd.gl_date
2980        ),
2981 last_updated_by = arp_global.last_updated_by,    /* Bug 2089972 */
2982 last_update_date = sysdate
2983  WHERE cust_trx_line_gl_dist_id  IN
2984        (SELECT MIN(DECODE(lgd3.gl_posted_date,
2985                           NULL, lgd3.cust_trx_line_gl_dist_id,
2986                           NULL) )
2987         FROM
2988                ra_cust_trx_line_gl_dist lgd3,
2989                ra_cust_trx_line_gl_dist rec3,
2990                ra_customer_trx t,
2991                ra_customer_trx_lines ctl
2995         AND    rec3.customer_trx_id      = t.customer_trx_id
2992         WHERE
2993                ctl.customer_trx_line_id  = p_customer_trx_line_id
2994         AND    t.customer_trx_id         = ctl.customer_trx_id
2996         AND    rec3.account_class        = 'REC'
2997         AND    rec3.latest_rec_flag      = 'Y'
2998         AND    (
2999                   ctl.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
3000                 OR
3001                   (ctl.line_type = 'LINE' AND ctl.accounting_rule_id IS NULL)
3002                )
3003         AND    lgd3.customer_trx_line_id = ctl.customer_trx_line_id
3004         AND    lgd3.account_set_flag     = 'N'
3005         AND    NVL(t.previous_customer_trx_id, -1) =
3006                 DECODE(p_trx_class_to_process,
3007                        'INV',        -1,
3008                        'REGULAR_CM', t.previous_customer_trx_id,
3009                        NVL(t.previous_customer_trx_id, -1) )
3010         GROUP BY
3011                  ctl.customer_trx_line_id,
3012                  DECODE(lgd3.account_class,'UNEARN','REV',lgd3.account_class),
3013                  lgd3.gl_date,
3014                  rec3.gl_date,
3015                  ctl.extended_amount,
3016                  ctl.revenue_amount,
3017                  t.exchange_rate
3018         HAVING (
3019                   SUM(NVL(lgd3.amount, 0))
3020                             <> DECODE(DECODE(lgd3.account_class,
3021                                              'UNEARN','REV',lgd3.account_class),
3022                                       'REV',       ctl.revenue_amount,
3023                                       'SUSPENSE',  ctl.extended_amount -
3024                                                    ctl.revenue_amount,
3025                                       ctl.extended_amount) *
3026                                DECODE(lgd3.gl_date,
3027                                       rec3.gl_date, 1,
3028                                       0)
3029                 OR
3030                   SUM(NVL(lgd3.acctd_amount, 0)) <>
3031                   DECODE(lgd3.gl_date,
3032                          rec3.gl_date, 1,
3033                          0) *
3034                   DECODE(p_base_mau,
3035                          NULL, ROUND(DECODE(DECODE(lgd3.account_class,
3036                                                    'UNEARN','REV',
3037                                                    lgd3.account_class),
3038                                             'REV',       ctl.revenue_amount,
3039                                             'SUSPENSE',  ctl.extended_amount -
3040                                                          ctl.revenue_amount,
3041                                             ctl.extended_amount) *
3042                                      NVL(t.exchange_rate,1),
3043                                      p_base_precision),
3044                          ROUND( (DECODE(DECODE(lgd3.account_class,
3045                                                'UNEARN','REV',
3046                                                lgd3.account_class),
3047                                             'REV',       ctl.revenue_amount,
3048                                             'SUSPENSE',  ctl.extended_amount -
3049                                                          ctl.revenue_amount,
3050                                             ctl.extended_amount) *
3051                                        NVL(t.exchange_rate,1)
3052                                 ) / p_base_mau
3053                               ) * p_base_mau
3054                         )
3055                )
3056        UNION
3057        SELECT TO_NUMBER(
3058                          MIN(DECODE(lgd5.gl_posted_date||lgd5.account_class||
3059                                     lgd5.account_set_flag,
3060                                      'REVN',     lgd5.cust_trx_line_gl_dist_id,
3061                                      'REVY',     lgd5.cust_trx_line_gl_dist_id,
3062                                      'TAXN',     lgd5.cust_trx_line_gl_dist_id,
3063                                      'TAXY',     lgd5.cust_trx_line_gl_dist_id,
3064                                      'FREIGHTN', lgd5.cust_trx_line_gl_dist_id,
3065                                      'FREIGHTY', lgd5.cust_trx_line_gl_dist_id,
3066                                      'CHARGESN', lgd5.cust_trx_line_gl_dist_id,
3067                                      'CHARGESY', lgd5.cust_trx_line_gl_dist_id,
3068                                      'UNEARNY',  lgd5.cust_trx_line_gl_dist_id,
3069                                      'UNBILLY',  lgd5.cust_trx_line_gl_dist_id,
3070                                      NULL) )
3071                        )
3072        FROM
3073               ra_cust_trx_line_gl_dist lgd5,
3074               ra_cust_trx_line_gl_dist rec5,
3075               ra_customer_trx_lines ctl2
3076        WHERE
3077               ctl2.customer_trx_line_id = p_customer_trx_line_id
3078        AND    rec5.customer_trx_id      = lgd5.customer_trx_id
3079        AND    rec5.account_class        = 'REC'
3080        AND    rec5.latest_rec_flag      = 'Y'
3081        AND    lgd5.customer_trx_line_id = ctl2.customer_trx_line_id
3082        AND    (
3083                   ctl2.line_type IN ('TAX', 'FREIGHT', 'CHARGES', 'SUSPENSE')
3084                 OR
3085                   (ctl2.line_type = 'LINE'   AND
3086                     (ctl2.accounting_rule_id IS NULL OR
3087                      lgd5.account_set_flag   = 'Y')
3088                   )
3089                )
3090        GROUP BY
3091                 lgd5.customer_trx_line_id,
3092                 lgd5.gl_date,
3093                 rec5.gl_date,
3097                        lgd5.account_class)
3094                 lgd5.account_set_flag,
3095                 DECODE(lgd5.account_set_flag,
3096                        'N', NULL,
3098        HAVING SUM(NVL(lgd5.percent, 0)) <>
3099               DECODE( NVL(lgd5.gl_date, rec5.gl_date),
3100                       rec5.gl_date, 100,
3101                       0)
3102        );
3103 
3104 
3105 
3106    END IF; /* customer_trx_line_id case */
3107 
3108    l_count := sql%rowcount;
3109 
3110    IF PG_DEBUG in ('Y', 'C') THEN
3111       arp_standard.debug(
3112           'Rows Processed: '||
3113           l_count);
3114    END IF;
3115 
3116    p_rows_processed := p_rows_processed + l_count;
3117 
3118    IF PG_DEBUG in ('Y', 'C') THEN
3119       arp_standard.debug( 'arp_rounding.correct_nonrule_line_records()- ' ||
3120                       TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3121    END IF;
3122 
3123   /* MRC Processing */
3124   IF PG_DEBUG in ('Y', 'C') THEN
3125      arp_standard.debug('doing rounding for MRC if necessary');
3126   END IF;
3127   ar_mrc_engine2.mrc_correct_rounding(
3128                    'CORRECT_NONRULE_LINE_RECORDS',
3129                    P_REQUEST_ID,
3130                    P_CUSTOMER_TRX_ID,
3131                    P_CUSTOMER_TRX_LINE_ID,
3132                    P_TRX_CLASS_TO_PROCESS
3133                   );
3134 
3135   RETURN( iTRUE );
3136  EXCEPTION
3137   WHEN others THEN
3138     p_error_message := SQLERRM;
3139     IF PG_DEBUG in ('Y', 'C') THEN
3140        arp_standard.debug('EXCEPTION:  arp_rounding.correct_nonrule_line_records failed()- '||
3141                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3142     END IF;
3143     RETURN(iFALSE);
3144 
3145 END correct_nonrule_line_records;
3146 
3147 /* Bug 2576253 - removed logic for FUNCTION correct_rule_records */
3148 
3149 /*-------------------------------------------------------------------------+
3150  | PRIVATE FUNCTION                                                        |
3151  |   correct_rule_records_by_line()                                        |
3152  |                                                                         |
3153  | DESCRIPTION                                                             |
3154  |   This function corrects errors in lines that use rules.                |
3155  |   It is a complete (from the ground up) rewrite of the logic in
3156  |   correct_rule_records.  The function correct_rule_records was designed
3157  |   to compensate for partially generated invoices (a norm in 10.7 and
3158  |   prior versions).  Accomodating that behavior resulted in very complex
3159  |   (and slow) logic.
3160  |
3161  |   The new function is broken into two pieces and relies upon bulk updates
3162  |   to update multiple rows at one time.  The first component is the
3163  |   driving cursor that identifies the specific lines that require rounding
3164  |   (customer_trx_line_id, account_class, amount, acctd_amount, and percent).
3165  |   The amount, acctd_amount, and percent are all DELTA values (the amount of
3166  |   rounding required.  To avoid problems with partially generated CMs (via
3167  |   ARTECMMB.pls, this logic will not round if the autorule_complete_flag is
3168  |   not null.  To avoid issues with old transactions, I now skip lines
3169  |   that have no unposted distributions.
3170  |
3171  |   The second component is an update statement that is fed by a second
3172  |   (included) subquery that identifies the specific gl_dist lines to update
3173  |   for each customer_trx_line_id.  This routine will always update the
3174  |   gl_dist line with the latest gl_date, highest amount, and if the prior
3175  |   two columns are the same, max(gl_dist_id).  This means that gl_dist_id
3176  |   is now only the tiebreaker, not the driving column.  For bug 2495595,
3177  |   we now only consider rows with posting_control_id = -3 to be recipients
3178  |   of rounding amounts.
3179  |
3180  |   Another noteworthy feature as of bug 2390821 is that we now round
3181  |   the REV, UNEARN (rec offset), and UNEARN (rev offset) separately.
3182  |   This was necessary because the original logic assummed (incorrectly)
3183  |   that the rec_offset UNEARN or UNBILL rows would be in balance naturally.
3184  |
3185  |   In bug 2480898, 2493896, and 2497841, we learned that older transactions
3186  |   that do not have rec_offset_flag set will be corrupted if they pass
3187  |   through the rounding logic again.  This happens if users manipulate
3188  |   the distributions of a completed and posted rule-based transaction.
3189  |   So, we now watch for transactions that do not have the rec_offset_flag
3190  |   set and set them where possible.  Will will not round a transaction line
3191  |   unless there is a rec_offset_flag=Y row for that line.
3192  |
3193  |   In bug 2535023 (see bug 2543675), we discovered that older versions of
3194  |   autoaccounting and unexpected behavior in ARXTWMAI can lead to situations
3195  |   where distributions are out of balance in interim (not last) period(s).
3196  |   When rounding fires, it would correct (but in last period) creating out
3197  |   of balance entries in two or more periods.  To prevent this, we included
3198  |   a new procedure called true_lines_by_gl_date to push rows back in synch
3199  |   before we actually round them for the line in total.
3200  |
3201  |   In bug 2449955, we figured out that we were not handling deferred
3202  |   lines on ARREARS invoices properly. We should treat them as if they
3203  |   were not deferred at all (just like conventional non-deferred rules).
3204  |
3205  |   In bugs 6325023 and 6473284, we learned that SLA will not post
3209  |   we added logic to detect these situations and to insert a separate
3206  |   distributions with entered and acctd amounts having opposite signs.
3207  |   Since this is possible for transactions that are not in functional
3208  |   currency with very small line amounts (<.20).  To resolve that,
3210  |   distributions to record amount and percent corrections and another
3211  |   distribution if the acctd_amount correction is the wrong sign.
3212  |
3213  |   For example, if the rounding correction would reverse the sign of
3214  |   the acctd_amount, then we will insert a separate distribution to
3215  |   record that correction.  However, if the entered and acctd corrections
3216  |   are themselves of opposite signs, then we'll insert one positive
3217  |   and a separate one with zero amount and negative acctd_amount.
3218  |
3219  |   This matrix helps explain what we round each line (by account_class)
3220  |   to:
3221  |
3222  |   CLASS  ROF  DEF   RULE   RESULT    NOTES
3223  |   REV    N    N     -2/-3  rev_amt
3224  |   REV    N    Y     -2     0         form adjustments
3225  |   REV    N    Y     -3     rev_amt
3226  |   UE     N    N     -2/-3  rev_amt*-1
3227  |   UE     Y    N     -2/-3  rev_amt
3228  |   UE     N    Y     -2     0         form adjustments
3229  |   UE     Y    Y     -2/-3  rev_amt
3230  |   UE     N    Y     -3     rev_amt   overrides deferred rules
3231  |
3232  | REQUIRES                                                                |
3233  |   All IN parameters                                                     |
3234  |                                                                         |
3235  | RETURNS                                                                 |
3236  |   TRUE  if no errors occur                                              |
3237  |   An ORACLE ERROR EXCEPTION if an ORACLE error occurs                   |
3238  |                                                                         |
3239  | NOTES                                                                   |
3240  |                                                                         |
3241  | EXAMPLE                                                                 |
3242  |                                                                         |
3243  | MODIFICATION HISTORY                                                    |
3244  |
3245  |  Created by bug 2150541
3246  |
3247  |   06-JUN-2002   M Raymond  2398021   Restructured both select and update
3248  |                                      to accomodate rounding of the
3249  |                                      rec_offset_rows.                   |
3250  |   09-JUL-2002   M Raymond  2445800   Added a where clause to accomodate
3251  |                                      CMs against invoices that have been
3252  |                                      reversed and regenerated by RAM.
3253  |   31-JUL-2002   M Raymond  2487744   Modified logic for deferred rules
3254  |                                      to round CMs against deferred invoices.
3255  |   02-AUG-2002   M Raymond  2492345   Exclude model rows when determining
3256  |                                      the max gl_date
3257  |   03-AUG-2002   M Raymond  2497841   Test and (when necessary) set the
3258  |                                      rec_offset_flag
3259  |                                      Added parameter for suppressing
3260  |                                      rec_offset_flag on calls from
3261  |                                      revenue recognition.
3262  |   20-AUG-2002   M Raymond  2480852   Change handling of deferred rules
3263  |                                      and revenue adjustments.
3264  |   20-AUG-2002   M Raymond  2480852   Exclude posted rows from being
3265  |                                      recipients of rounding amounts.
3266  |   26-AUG-2002   M Raymond  2532648   Exclude posted rows from rounding
3267  |                                      completely.
3268  |   27-AUG-2002   M Raymond  2532648   Re-implemented skipping of lines
3269  |                                      bearing deferred rules.
3270  |   04-SEP-2002   M Raymond  2535023   Revised SELECT to carefully round
3271  |                                      form adjustments on deferred rule lines
3272  |                                      to zero instead of extended amount.
3273  |   05-SEP-2002   M Raymond  2535023   Added a separate private procedure
3274  |                                      called true_lines_by_gl_date.  Now
3275  |                                      calling this routine to make sure
3276  |                                      gl_dates in all periods balance before
3277  |                                      I round the line in total.
3278  |   10-SEP-2002   M Raymond  2559944   Not handling deferred lines for
3279  |                                      ARREARS invoices properly.  Revised
3280  |                                      CURSOR to properly ignore defers
3281  |                                      on ARREARS invoices.
3282  |   13-SEP-2002   M Raymond  2543576   Switched from extended_amount to
3283  |                                      revenue_amount.  This accomodates
3284  |                                      situations where suspense accounts are
3285  |                                      in use.  Just FYI, ext_amt = qty * prc
3286  |                                      and rev_amt can equal ext_amt unless
3287  |                                      the user passed a different ext_amt
3288  |                                      via autoinvoice and had clearing
3289  |                                      enabled.  The amt passed by user
3290  |                                      and used for line is stored in
3294  |                                      changed SELECT to exclude rule-based
3291  |                                      revenue_amount
3292  |   14-SEP-2002   M Raymond  2569870   Prevented RAM dists from being
3293  |                                      recipient of rounding (UPDATE).  Also
3295  |                                      lines when no rec_offset row exists.
3296  |   06-MAR-2003   M Raymond  2632863   Fixed rounding errors when dist in
3297  |                                      last period was of opposite sign
3298  |                                      ex: CM vs .2/12 invoice
3299  |   02-OCT-2003   M Raymond  3033850/3067588
3300  |                                      Modified code to execute three times
3301  |                                      for same, opposite, and zero rounding.
3302  |                                      Also removed sign subquery.
3303  |   04-MAY-2004   M Raymond  3605089   Added logic for SUSPENSE to this
3304  |                                      logic to round for salescredit
3305  |                                      splits.  later removed logic as
3306  |                                      it does not resolve issue at hand.
3307  |                                      See ARPLCREB.pls 115.64 if SUSPENSE
3308  |                                      rounding comes in conjunction with
3309  |                                      salescredits.
3310  |   06-OCT-2007   M Raymond  6325023/6473284 - Added logic to handle
3311  |                                      unusual rounding issues for
3312  |                                      acctd amounts.
3313  +-------------------------------------------------------------------------*/
3314 
3315 FUNCTION correct_rule_records_by_line(
3316 		P_REQUEST_ID           IN NUMBER,
3317                 P_CUSTOMER_TRX_ID      IN NUMBER,
3318                 P_ROWS_PROCESSED       IN OUT NOCOPY NUMBER,
3319                 P_ERROR_MESSAGE        OUT NOCOPY VARCHAR2,
3320                 P_BASE_PRECISION       IN NUMBER,
3321                 P_BASE_MAU             IN NUMBER,
3322                 P_TRX_CLASS_TO_PROCESS IN VARCHAR2,
3323                 P_CHECK_RULES_FLAG     IN VARCHAR2,
3324                 P_PERIOD_SET_NAME      IN OUT NOCOPY VARCHAR2,
3325                 P_FIX_REC_OFFSET       IN VARCHAR2 DEFAULT 'Y')
3326 
3327          RETURN NUMBER IS
3328 
3329   t_line_id       l_line_id_type;
3330   t_gl_id         l_line_id_type;
3331   t_round_amount  l_amount_type;
3332   t_round_percent l_percent_type;
3333   t_round_acctd   l_amount_type;
3334   t_account_class l_acct_class;
3335   t_rec_offset    l_rec_offset;
3336 
3337   l_rows_needing_rounding NUMBER;
3338   l_rows_rounded NUMBER := 0;
3339   l_rows_rounded_this_pass NUMBER := 0;
3340   l_phase NUMBER := 0;
3341 
3342   l_result NUMBER;
3343   /* Cursor for FINAL rounding
3344      Detects which customer_trx_line_ids require rounding
3345      and determines the amount, acctd_amount, and percent
3346      for each account_class */
3347 
3348   /* Dev note:  The EXISTS clause for rec_offset_flag (rof)
3349      was added as a precaution.  It has a noticable impact on
3350      the explain plan - so it may be necessary to remove it
3351      if performance becomes an issue in this code.  An alternative
3352      would be to put it in the UPDATE instead, thus limiting the number
3353      of times it gets called.*/
3354 
3355   CURSOR round_rows_by_trx(p_trx_id NUMBER,
3356                            p_base_mau NUMBER,
3357                            p_base_precision NUMBER) IS
3358   select l.customer_trx_line_id, g.account_class,
3359          /* AMOUNT LOGIC */
3360          (DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3361              DECODE(r.deferred_revenue_flag, 'Y',
3362                 DECODE(t.invoicing_rule_id, -2, 0, l.revenue_amount),
3363                l.revenue_amount))
3364           - (sum(g.amount) *
3365                DECODE(g.account_class, 'REV', 1,
3366                   DECODE(g.rec_offset_flag, 'Y', 1, -1))))
3367                      * DECODE(g.account_class, 'REV', 1,
3368                           DECODE(g.rec_offset_flag, 'Y', 1, -1))  ROUND_AMT,
3369          /* PERCENT LOGIC */
3370          (DECODE(g.rec_offset_flag, 'Y', 100,
3371              DECODE(r.deferred_revenue_flag, 'Y',
3372                 DECODE(t.invoicing_rule_id, -2, 0, 100),
3373                 100))
3374           - (sum(g.percent) *
3375                DECODE(g.account_class, 'REV', 1,
3376                  DECODE(g.rec_offset_flag, 'Y', 1, -1))))
3377                   * DECODE(g.account_class, 'REV', 1,
3378                       DECODE(g.rec_offset_flag, 'Y', 1, -1))  ROUND_PCT,
3379          /* ACCTD_AMOUNT LOGIC */
3380          (DECODE(p_base_mau, NULL,
3381             ROUND(DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3382                      DECODE(r.deferred_revenue_flag, 'Y',
3383                         DECODE(t.invoicing_rule_id, -2, 0, l.revenue_amount),
3384                              l.revenue_amount))
3385                    * nvl(t.exchange_rate,1), p_base_precision),
3386             ROUND((DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3387                       DECODE(r.deferred_revenue_flag, 'Y',
3388                         DECODE(t.invoicing_rule_id, -2, 0, l.revenue_amount),
3389                              l.revenue_amount))
3390                    * nvl(t.exchange_rate,1)) / p_base_mau) * p_base_mau)
3391           - (sum(g.acctd_amount) *
3392                DECODE(g.account_class, 'REV', 1,
3393                  DECODE(g.rec_offset_flag, 'Y', 1, -1))))
3397          g.rec_offset_flag
3394                   * DECODE(g.account_class, 'REV', 1,
3395                       DECODE(g.rec_offset_flag, 'Y', 1, -1))  ROUND_ACCT_AMT,
3396          /* END ACCTD_AMOUNT LOGIC */
3398   from   ra_customer_trx_lines l,
3399          ra_cust_trx_line_gl_dist g,
3400          ra_customer_trx t,
3401          ra_rules r
3402   where  t.customer_trx_id = p_trx_id
3403   and    l.customer_trx_id = t.customer_trx_id
3404   and    l.customer_trx_id = g.customer_trx_id
3405   and    l.customer_trx_line_id = g.customer_trx_line_id
3406          /* Skip any entries created by revenue adjustments
3407             or for deferred rules */
3408   and    l.accounting_rule_id = r.rule_id
3409   and    g.revenue_adjustment_id is NULL
3410          /* Only round transaction lines with rules */
3411   and    l.accounting_rule_id is not NULL
3412   and    l.autorule_complete_flag is NULL
3413   and    g.account_class IN ('REV','UNEARN','UNBILL')
3414   and    g.account_set_flag = 'N'
3415          /* Only round lines that actually have a rec_offset row */
3416   and exists ( SELECT 'has rof row'
3417                FROM   ra_cust_trx_line_gl_dist rof
3418                WHERE  rof.customer_trx_line_id = g.customer_trx_line_id
3419                AND    rof.account_set_flag = 'N'
3420                AND    rof.account_class in ('UNEARN','UNBILL')
3421                AND    rof.rec_offset_flag = 'Y')
3422   having
3423          /* AMOUNT LOGIC */
3424          (sum(g.amount) <>  DECODE(g.account_class, 'REV', l.revenue_amount,
3425                               DECODE(g.rec_offset_flag, 'Y', l.revenue_amount,
3426                                              l.revenue_amount * -1)) *
3427                   DECODE(r.deferred_revenue_flag, 'Y',
3428                     DECODE(g.rec_offset_flag, 'Y', 1,
3429                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) or
3430          /* PERCENT LOGIC */
3431          sum(g.percent) <> DECODE(g.account_class, 'REV', 100,
3432                             DECODE(g.rec_offset_flag, 'Y', 100, -100)) *
3433                   DECODE(r.deferred_revenue_flag, 'Y',
3434                     DECODE(g.rec_offset_flag, 'Y', 1,
3435                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) or
3436          /* ACCTD_AMOUNT LOGIC */
3437          sum(g.acctd_amount) <> DECODE(p_base_mau, NULL,
3438                     ROUND(l.revenue_amount * nvl(t.exchange_rate,1), p_base_precision),
3439                     ROUND((l.revenue_amount * nvl(t.exchange_rate,1)) /
3440                                             p_base_mau) * p_base_mau) *
3441                   DECODE(r.deferred_revenue_flag, 'Y',
3442                     DECODE(g.rec_offset_flag, 'Y', 1,
3443                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) *
3444                   DECODE(g.account_class, 'REV', 1,
3445                     DECODE(g.rec_offset_flag, 'Y', 1, -1)))
3446          /* Only round lines w/unposted distributions */
3447   and    min(g.posting_control_id) = -3
3448 group by l.customer_trx_line_id, g.account_class, g.rec_offset_flag,
3449          l.revenue_amount, t.exchange_rate, r.deferred_revenue_flag,
3450          t.invoicing_rule_id;
3451 
3452 BEGIN
3453 
3454   IF PG_DEBUG in ('Y', 'C') THEN
3455      arp_standard.debug( 'arp_rounding.correct_rule_records_by_line()+ ' ||
3456                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3457   END IF;
3458 
3459   IF (P_CUSTOMER_TRX_ID IS NOT NULL) THEN
3460     /* Form and Rev Rec variant */
3461 
3462     IF (P_FIX_REC_OFFSET = 'Y') THEN
3463        /* Verify that rec_offset_flag(s) are set for this transaction
3464           and set them if they are not */
3465        set_rec_offset_flag(p_customer_trx_id, null, l_result);
3466 
3467        IF PG_DEBUG in ('Y', 'C') THEN
3468            arp_standard.debug('  result from set_rec_offset_flag() call : ' || l_result);
3469        END IF;
3470 
3471     END IF;
3472 
3473      /* This is phase 1 of rounding.
3474         Here, we make sure that debits equal credits (REV and UNEARN dists)
3475         on a gl_date basis.  We do this for both RAM and conventional
3476         distributions.  If there is a problem, we correct it
3477         on that date. */
3478      true_lines_by_gl_date(p_customer_trx_id);
3479 
3480      /* This is phase 2 of rounding.
3481         With this cursor and subsequent UPDATE, we detect situations
3482         where REV, UNEARN, or UNEARN(rof) for each line do not total
3483         to the revenue_amount of the line.  This routine assumes that
3484         the previous one has executed and that everything is already
3485         in balance by gl_date.
3486 
3487         NOTE:  Under normal circumstances, this routine will only make
3488         changes to distributions as part of Revenue Recognition.  It
3489         should not make changes based on form-level adjustments or
3490         RAM adjustments (after Revenue Recognition has completed).
3491 
3492         As of bug 3033850, I revised the rounding logic to execute up
3493         to three separate times/phases to handle unusual cases (opposite sign,
3494         zero dists)  The code will execute first for same sign rounding,
3495         then opposite sign, and finally, using zero sign dists.  The code
3496         should be able to detect if rounding is complete and exit after
3497         having rounded all the distributions.  Even if only 1 or two phases
3498         have been completed.
3499 
3500         The phases/passes are:
3501           1=Dists with same sign as line (UPDATE)
3502           2=Dists with opposite sign as line (UPDATE)
3506 
3503           3=Dists with zero amount (when line is non-zero) (UPDATE)
3504           4=Dists where corrections cause signs to mismatch (+/-) (INSERT)
3505           5=Continuation of 4, corrections themselves have opposite signs (INSERT)
3507         Note:  phase 4 and 5 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 < 5 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 <= 3
3563         THEN
3564           FORALL i IN t_line_id.FIRST .. t_line_id.LAST
3565             UPDATE ra_cust_trx_line_gl_dist
3566             SET    amount = amount + t_round_amount(i),
3567                    percent = percent + t_round_percent(i),
3568                    acctd_amount = acctd_amount + t_round_acctd(i),
3569                    last_updated_by = arp_global.last_updated_by,
3570                    last_update_date = sysdate
3571             WHERE  cust_trx_line_gl_dist_id in (
3572                /* SELECT GL_DIST_ID FOR EACH LINE THAT
3573                   REQUIRES ROUNDING */
3574                select MAX(g.cust_trx_line_gl_dist_id)
3575                from   ra_cust_trx_line_gl_dist g,
3576                       ra_cust_trx_line_gl_dist gmax,
3577                       ra_customer_trx_lines tl
3578                where  g.customer_trx_line_id = t_line_id(i)
3579                and    tl.customer_trx_line_id = g.customer_trx_line_id
3580                and    g.account_class = t_account_class(i)
3581                and    g.account_set_flag = 'N'
3582                       /* ONLY USE UNPOSTED ROWS */
3583                and    g.posting_control_id = -3
3584                       /* ONLY CONSIDERS REC_OFFSET_FLAG IF NOT NULL */
3585                and    nvl(g.rec_offset_flag, '~') = nvl(t_rec_offset(i), '~')
3586                       /* FORCES USE OF ROW IN LAST PERIOD */
3587                and    g.gl_date = (
3588                           select max(gl_date)
3589                           from ra_cust_trx_line_gl_dist gdmax
3590                           where gdmax.customer_trx_line_id = g.customer_trx_line_id
3591                           and   gdmax.account_class = g.account_class
3592                           and   nvl(gdmax.rec_offset_flag, '~') =
3593                                           nvl(g.rec_offset_flag, '~')
3594                           and   gdmax.account_set_flag = 'N'
3595                           and   gdmax.posting_control_id = -3
3596                           and   gdmax.revenue_adjustment_id is null)
3597                and    gmax.customer_trx_line_id = g.customer_trx_line_id
3598                and    gmax.account_class = g.account_class
3599                and    gmax.account_set_flag = 'N'
3600                and    nvl(gmax.rec_offset_flag, '~') =
3601                       nvl(g.rec_offset_flag, '~')
3602                and    gmax.gl_date = g.gl_date
3603                       /* DO NOT ROUND RAM DISTRIBUTIONS */
3604                and    g.revenue_adjustment_id is null
3605                and    gmax.revenue_adjustment_id is null
3606                       /* USE DISTS THAT MATCH SIGN OF LINE FIRST,
3607                          THEN OTHERS (ZERO, NEGATIVE).*/
3608                and    (SIGN(g.amount) = SIGN(tl.revenue_amount) *
3609                                    DECODE(g.account_class, 'REV', 1,
3610                                       DECODE(g.rec_offset_flag, 'Y', 1, -1)) *
3611                                    DECODE(l_phase, 1, 1, 2, -1, 0))
3612                       /* SKIP UPDATE IF SIGNS AR OPPOSITE */
3613                and   (sign(g.amount + t_round_amount(i)) =
3614                       sign(g.acctd_amount + t_round_acctd(i)) or
3615                       sign(g.amount + t_round_amount(i)) = 0)
3619                                                          1, MAX(gmax.amount),
3616                having
3617                       /* USE LINE WITH LARGEST ABS(AMOUNT) */
3618                       g.amount = decode(sign(g.amount), -1, MIN(gmax.amount),
3620                                                         0)
3621                group by g.amount
3622                /* END OF GL_DIST_ID SELECT */
3623                );
3624         ELSE
3625            /* 6325023 - added 4th phase to handle SLA issues where
3626               entered and acctd_amount dists have opposite signs */
3627            /* 6473284 - Added 5th phase to extend fix for 6325023 to
3628                cover some odd corner cases. */
3629 
3630 
3631            FORALL i in t_line_id.first .. t_line_id.last
3632             INSERT INTO RA_CUST_TRX_LINE_GL_DIST
3633               (CUST_TRX_LINE_GL_DIST_ID,
3634                CREATED_BY,
3635                CREATION_DATE,
3636                LAST_UPDATED_BY,
3637                LAST_UPDATE_DATE,
3638                LAST_UPDATE_LOGIN,
3639                PROGRAM_APPLICATION_ID,
3640                PROGRAM_ID,
3641                PROGRAM_UPDATE_DATE,
3642                POSTING_CONTROL_ID,
3643                SET_OF_BOOKS_ID,
3644                CUSTOMER_TRX_LINE_ID,
3645                CUSTOMER_TRX_ID,
3646                ACCOUNT_CLASS,
3647                CODE_COMBINATION_ID,
3648                AMOUNT,
3649                ACCTD_AMOUNT,
3650                PERCENT,
3651                GL_DATE,
3652                ORIGINAL_GL_DATE,
3653                ACCOUNT_SET_FLAG,
3654                COMMENTS,
3655                ATTRIBUTE_CATEGORY,
3656                ATTRIBUTE1,
3657                ATTRIBUTE2,
3658                ATTRIBUTE3,
3659                ATTRIBUTE4,
3660                ATTRIBUTE5,
3661                ATTRIBUTE6,
3662                ATTRIBUTE7,
3663                ATTRIBUTE8,
3664                ATTRIBUTE9,
3665                ATTRIBUTE10,
3666                ATTRIBUTE11,
3667                ATTRIBUTE12,
3668                ATTRIBUTE13,
3669                ATTRIBUTE14,
3670                ATTRIBUTE15,
3671                LATEST_REC_FLAG,
3672                USSGL_TRANSACTION_CODE,
3673                REC_OFFSET_FLAG,
3674                USER_GENERATED_FLAG,
3675                ORG_ID,
3676                REQUEST_ID,
3677                CUST_TRX_LINE_SALESREP_ID,
3678                ROUNDING_CORRECTION_FLAG
3679               )
3680         SELECT
3681             RA_CUST_TRX_LINE_GL_DIST_S.NEXTVAL,
3682             CREATED_BY,
3683             CREATION_DATE,
3684             LAST_UPDATED_BY,
3685             LAST_UPDATE_DATE,
3686             LAST_UPDATE_LOGIN,
3687             PROGRAM_APPLICATION_ID,
3688             PROGRAM_ID,
3689             PROGRAM_UPDATE_DATE,
3690             -3,
3691             SET_OF_BOOKS_ID,
3692             CUSTOMER_TRX_LINE_ID,
3693             CUSTOMER_TRX_ID,
3694             ACCOUNT_CLASS,
3695             CODE_COMBINATION_ID,
3696             DECODE(l_phase, 4, t_round_amount(i), 0),
3697             DECODE(l_phase, 4,
3698               DECODE(SIGN(t_round_amount(i)),0,t_round_acctd(i),
3699                    ABS(t_round_acctd(i)) * SIGN(t_round_amount(i))),
3700               t_round_acctd(i) * 2),
3701             DECODE(l_phase, 4, t_round_percent(i), 0),
3702             GL_DATE,
3703             ORIGINAL_GL_DATE,
3704             ACCOUNT_SET_FLAG,
3705             'PHASE ' || l_phase || ':  Rounding correction derived from ' ||
3706                cust_trx_line_gl_dist_id,
3707             ATTRIBUTE_CATEGORY,
3708             ATTRIBUTE1,
3709             ATTRIBUTE2,
3710             ATTRIBUTE3,
3711             ATTRIBUTE4,
3712             ATTRIBUTE5,
3713             ATTRIBUTE6,
3714             ATTRIBUTE7,
3715             ATTRIBUTE8,
3716             ATTRIBUTE9,
3717             ATTRIBUTE10,
3718             ATTRIBUTE11,
3719             ATTRIBUTE12,
3720             ATTRIBUTE13,
3721             ATTRIBUTE14,
3722             ATTRIBUTE15,
3723             LATEST_REC_FLAG,
3724             USSGL_TRANSACTION_CODE,
3725             REC_OFFSET_FLAG,
3726             USER_GENERATED_FLAG,
3727             ORG_ID,
3728             REQUEST_ID,
3729             CUST_TRX_LINE_SALESREP_ID,
3730             'Y'
3731         FROM  RA_CUST_TRX_LINE_GL_DIST_ALL
3732         WHERE CUST_TRX_LINE_GL_DIST_ID IN (
3733               /* SELECT GL_DIST_ID FOR EACH LINE THAT
3734                  REQUIRES ROUNDING */
3735               select
3736                 to_number(substr(max(
3737                        to_char(g.gl_date,'YYYYMMDD') ||
3738                        decode(sign(g.amount *
3739                                  DECODE(g.account_class, 'REV', 1,
3740                                    DECODE(g.rec_offset_flag, 'Y', 1, -1))),
3741                               sign(tl.revenue_amount), '3',
3742                            sign(tl.revenue_amount * -1), '2', '1') ||
3743                        ltrim(to_char(abs(g.amount),'099999999999999.00')) ||
3744                        ltrim(to_char(g.cust_trx_line_gl_dist_id,
3745                                           '0999999999999999999999'))),28))
3746               from   ra_cust_trx_line_gl_dist g,
3747                      ra_customer_trx_lines tl
3748               where  g.customer_trx_line_id = t_line_id(i)
3752                      /* ONLY USE UNPOSTED ROWS */
3749               and    tl.customer_trx_line_id = g.customer_trx_line_id
3750               and    g.account_class = t_account_class(i)
3751               and    g.account_set_flag = 'N'
3753               and    g.posting_control_id = -3
3754                      /* ONLY CONSIDERS REC_OFFSET_FLAG IF NOT NULL */
3755               and    nvl(g.rec_offset_flag, '~') = nvl(t_rec_offset(i), '~')
3756                      /* DO NOT ROUND RAM DISTRIBUTIONS */
3757               and    g.revenue_adjustment_id is null
3758               /* END OF GL_DIST_ID SELECT */
3759               );
3760 
3761         END IF;
3762 
3763        l_rows_rounded_this_pass := 0;
3764 
3765        /* START - Cleanup loop */
3766        FOR upd in t_line_id.FIRST .. t_line_id.LAST LOOP
3767 
3768           IF(SQL%BULK_ROWCOUNT(upd) = 1)
3769           THEN
3770 
3771           /* This piece of code determines that 1 row was updated
3772              for each invoice line and account class.  Once the
3773              row is updated, we need to remove it from further
3774              consideration.  To do that, we change the line_id
3775              to line_id * -1 (a row that should never exist)
3776              and this prevents it from being processed in
3777              subsequent passes.
3778 
3779              Incidentally, I tried to just delete the
3780              processed rows - but this caused subsequent
3781              passes to fail with ORA errors due to missing
3782              plsql table rows.  The bulk update requires
3783              a continuous list in sequential order and, by deleting
3784              rows from the table, we cause the update to fail.
3785           */
3786 
3787               IF PG_DEBUG in ('Y', 'C') THEN
3788                  arp_standard.debug('  Target: ' || t_line_id(upd) ||
3789                                 '  ' || t_account_class(upd) ||
3790                                 '  ' || t_rec_offset(upd) ||
3791                                 '  ' || t_round_amount(upd) ||
3792                                 '  ' || t_round_acctd(upd) ||
3793                                 ' ' || t_round_percent(upd) ||
3794                                 ' ' || SQL%BULK_ROWCOUNT(upd));
3795               END IF;
3796 
3797 
3798               IF l_phase = 4
3799               THEN
3800                  /* extra checks to see if we need last phase */
3801                  IF t_round_amount(upd) = 0
3802                     OR  t_round_acctd(upd) = 0
3803                     OR  SIGN(t_round_amount(upd)) = SIGN(t_round_acctd(upd))
3804                  THEN
3805                     /* This phase inserted complete dists
3806                        so no need to insert another dist */
3807                     l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
3808                     t_line_id(upd) := -1 * t_line_id(upd);
3809                  ELSE
3810                     /* Do not change the line_id or increment.. this
3811                         forces the last phase and an insert of
3812                         a dist with amount=0 and acctd_amount=<correction * 2>
3813                     */
3814                     NULL;
3815                  END IF;
3816               ELSE
3817                  /* previous behavior */
3818                  l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
3819                  /* make line_id negative so it causes no further updates */
3820                  t_line_id(upd) := -1 * t_line_id(upd);
3821               END IF;
3822           END IF;
3823 
3824           IF(SQL%BULK_ROWCOUNT(upd) > 1)
3825           THEN
3826              /* Failure condition 1
3827                 This section of code executes only when more than
3828                 one line is updated for a given customer_trx_line_id
3829                 and account_class.  That would mean that the rounding
3830                 logic was unable to identify a single line for update
3831                 and rounding would then raise an error to roll back
3832                 any corrections or calculations for this transaction.
3833 
3834                 Revenue recognition has been modified to roll back
3835                 transactions that fail and to document the lines
3836                 that have problems.  */
3837 
3838              IF PG_DEBUG in ('Y', 'C')
3839              THEN
3840 
3841                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
3842                    arp_standard.debug(t_line_id(err)|| '  ' ||
3843                                       t_account_class(err) ||
3844                      '  ' || t_rec_offset(err) ||
3845                      '  ' || t_round_amount(err) ||
3846                      ' ' || t_round_acctd(err) || ' ' ||
3847                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
3848                 END LOOP;
3849 
3850              END IF;
3851 
3852              p_error_message := 'arp.rounding:  Error identifying rows for correction.  trx_id = ' || p_customer_trx_id;
3853 
3854              RETURN(iFALSE);
3855 
3856           END IF;
3857 
3858        END LOOP; /* END - Cleanup loop */
3859 
3860        IF PG_DEBUG in ('Y', 'C') THEN
3861           arp_standard.debug('    Rows rounded this pass : ' || l_rows_rounded_this_pass);
3862        END IF;
3863 
3864        l_rows_rounded := l_rows_rounded + l_rows_rounded_this_pass;
3865 
3866      END LOOP;  /* END - Main processing loop */
3867 
3868        IF (l_rows_needing_rounding <> l_rows_rounded) THEN
3869 
3870           /* Failure condition 2
3874              locate any rows to assess rounding corrections to for
3871              In this situation, the total number of distributions corrected
3872              does not match the number expected.  Because of condition 1
3873              handled above, this would only occur if we were unable to
3875              one or more invoice lines.  Such situations highlight
3876              shortcomings in this logic that must be investigated
3877              and corrected.
3878           */
3879 
3880           IF PG_DEBUG in ('Y', 'C') THEN
3881              arp_standard.debug('Mismatch between lines found and lines updated (see below)');
3882              arp_standard.debug('  Rows targeted: ' || l_rows_needing_rounding);
3883              arp_standard.debug('  Rows rounded : ' || l_rows_rounded);
3884 
3885              FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
3886 
3887                  arp_standard.debug(t_line_id(err) || '  ' || t_account_class(err) ||
3888                      '  ' || t_rec_offset(err) ||
3889                      '  ' || t_round_amount(err) || ' ' || t_round_acctd(err) || ' ' ||
3890                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
3891 
3892              END LOOP;
3893 
3894           END IF;
3895 
3896             p_error_message := ' arp_rounding: Error identifying rows for correction. ' ||
3897                                ' trx_id = ' || p_customer_trx_id;
3898 
3899           RETURN(iFALSE);
3900        END IF;
3901 
3902        p_rows_processed := p_rows_processed + l_rows_rounded;
3903        IF PG_DEBUG in ('Y', 'C') THEN
3904           arp_standard.debug('Total number of rows updated:  ' || l_rows_rounded);
3905        END IF;
3906 
3907   /* MRC Processing */
3908   IF PG_DEBUG in ('Y', 'C') THEN
3909      arp_standard.debug('doing rounding for MRC if necessary');
3910   END IF;
3911   ar_mrc_engine2.mrc_correct_rounding(
3912                    'CORRECT_RULE_RECORDS_BY_LINE',
3913                    P_REQUEST_ID,
3914                    P_CUSTOMER_TRX_ID,
3915                    NULL,    /* customer trx line id */
3916                    P_TRX_CLASS_TO_PROCESS,
3917          	   NULL,   /* concat_segs */
3918                    NULL,  /* balanced round_ccid */
3919                    p_check_rules_flag,
3920                    p_period_set_name
3921                   );
3922 
3923   END IF;
3924 
3925   IF PG_DEBUG in ('Y', 'C') THEN
3926      arp_standard.debug('arp_rounding.correct_rule_records_by_line()- ' ||
3927                      TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
3928   END IF;
3929 
3930   RETURN(iTRUE);
3931 END correct_rule_records_by_line;
3932 
3933 /*-------------------------------------------------------------------------+
3934  | PRIVATE FUNCTION                                                        |
3935  |   correct_rev_adj_by_line()                                        |
3936  |                                                                         |
3937  | DESCRIPTION                                                             |
3938  |   This function corrects rounding errors resulting from revenue
3939  |   adjustments created via ar_revenue_adjustment_pvt.dists_by_model
3940  |   routine.  The logic contained below is almost identical to
3941  |   correct_rule_records_by_line (although it has been altered to
3942  |   drive from AR_LINE_REV_ADJ_GT table (capable of rounding
3943  |   multiple transactions or adjustments at one time).
3944  |
3945  |   See description of correct_rule_records_by_line for details about
3946  |   the architecture of this function.
3947  |
3948  |   NOTE:  Due to the unique data available for RAM adjustments, it was
3949  |   not possible to round percents consistently at this time.  amount and
3950  |   acctd_amount columns will be rounded -- but percents will not.
3951  +-------------------------------------------------------------------------*/
3952 
3953 FUNCTION correct_rev_adj_by_line
3954         RETURN NUMBER IS
3955 
3956   t_line_id       l_line_id_type;
3957   t_gl_id         l_line_id_type;
3958   t_round_amount  l_amount_type;
3959   t_round_percent l_percent_type;
3960   t_round_acctd   l_amount_type;
3961   t_account_class l_acct_class;
3962   t_rev_adj_id    l_line_id_type;
3963 
3964   l_rows_needing_rounding NUMBER;
3965   l_rows_rounded NUMBER := 0;
3966   l_rows_rounded_this_pass NUMBER := 0;
3967   l_phase NUMBER := 0;
3968 
3969   /* Cursor for FINAL rounding
3970      Detects which customer_trx_line_ids require rounding
3971      and determines the amount, acctd_amount, and percent
3972      for each account_class */
3973 
3974   CURSOR round_rows_by_trx(p_base_mau NUMBER,
3975                            p_base_precision NUMBER) IS
3976   select /*+ leading(gt t) index(l ra_customer_trx_lines_u1) index(g ra_cust_trx_line_gl_dist_n1)*/
3977          l.customer_trx_line_id, g.account_class,
3978          /* AMOUNT LOGIC */
3979          (gt.amount
3980           - (sum(g.amount)
3981               * DECODE(g.account_class, 'REV',1,-1)))
3982                  * DECODE(g.account_class, 'REV',1,-1)        ROUND_AMT,
3983          /* END AMOUNT LOGIC */
3984          /* Leaving percent alone for now */
3985          0                                                    ROUND_PCT,
3986          /* ACCTD_AMOUNT LOGIC */
3987          (DECODE(p_base_mau, NULL,
3988             ROUND(gt.amount
3989                * nvl(t.exchange_rate,1), p_base_precision),
3993           - (sum(g.acctd_amount)
3990             ROUND((gt.amount
3991                * nvl(t.exchange_rate,1))
3992                     / p_base_mau) * p_base_mau)
3994                * DECODE(g.account_class, 'REV', 1, -1)))
3995                   * DECODE(g.account_class, 'REV', 1, -1)     ROUND_ACCT_AMT,
3996          /* END ACCTD_AMOUNT LOGIC */
3997          gt.revenue_adjustment_id
3998   from   ra_customer_trx_lines    l,
3999          ar_line_rev_adj_gt       gt,
4000          ra_cust_trx_line_gl_dist g,
4001          ra_customer_trx          t
4002   where  t.customer_trx_id = gt.customer_trx_id
4003   and    l.customer_trx_id = t.customer_trx_id
4004   and    l.customer_trx_id = g.customer_trx_id
4005   and    l.customer_trx_line_id = g.customer_trx_line_id
4006 /* Bug Number 6782307 -- Added the below join condition */
4007   and    l.customer_trx_line_id = gt.customer_trx_line_id
4008   and    g.revenue_adjustment_id = gt.revenue_adjustment_id
4009   and    l.autorule_complete_flag is NULL
4010   and    g.account_class IN ('REV','UNEARN','UNBILL')
4011   and    g.account_set_flag = 'N'
4012   having
4013          /* AMOUNT LOGIC */
4014          (sum(g.amount) <>  gt.amount *
4015                    DECODE(g.account_class, 'REV',1,-1) or
4016          /* PERCENT LOGIC
4017          sum(g.percent) <> DECODE(g.account_class, 'REV', 100,
4018                             DECODE(g.rec_offset_flag, 'Y', 100, -100)) *
4019                   DECODE(r.deferred_revenue_flag, 'Y',
4020                     DECODE(g.rec_offset_flag, 'Y', 1,
4021                       DECODE(t.invoicing_rule_id, -2, 0, 1)),1) or */
4022          /* ACCTD_AMOUNT LOGIC */
4023          sum(g.acctd_amount) <> DECODE(p_base_mau, NULL,
4024                     ROUND(gt.amount
4025                        * nvl(t.exchange_rate,1), p_base_precision),
4026                     ROUND((gt.amount
4027                        * nvl(t.exchange_rate,1)) /
4028                                p_base_mau) * p_base_mau) *
4029                   DECODE(g.account_class, 'REV', 1,-1))
4030          /* Only round lines w/unposted distributions */
4031   and    min(g.posting_control_id) = -3
4032 group by l.customer_trx_line_id, g.account_class,
4033          gt.revenue_adjustment_id, gt.amount, t.exchange_rate;
4034 
4035 BEGIN
4036 
4037   IF PG_DEBUG in ('Y', 'C') THEN
4038      arp_standard.debug('arp_rounding.correct_rev_adj_by_line()+ ');
4039   END IF;
4040 
4041      /* This is phase 1 of rounding.
4042         Here, we make sure that debits equal credits (REV and UNEARN dists)
4043         on a gl_date basis.  We do this for both RAM and conventional
4044         distributions.  If there is a problem, we correct it
4045         on that date. */
4046 
4047      /* Passing null to this routine forces it to drive using a join
4048         to ar_line_rev_adj_gt table */
4049      true_lines_by_gl_date(null);
4050 
4051      /* This is phase 2 of rounding.
4052         With this cursor and subsequent UPDATE, we detect situations
4053         where REV or UNEARN for each line do not total
4054         to the adjustment amount of the line.  This routine assumes that
4055         the previous one has executed and that everything is already
4056         in balance by gl_date.
4057 
4058         The phases are 1=Dists with same sign as line
4059                        2=Dists with opposite sign as line
4060                        3=Dists with zero amount (when line is non-zero
4061                        4=Dists where acctd_amount sign changes */
4062 
4063      OPEN round_rows_by_trx(AR_RAAPI_UTIL.g_min_acc_unit,
4064                             AR_RAAPI_UTIL.g_trx_precision);
4065 	FETCH round_rows_by_trx BULK COLLECT INTO
4066                              t_line_id,
4067                              t_account_class,
4068                              t_round_amount,
4069                              t_round_percent,
4070                              t_round_acctd,
4071                              t_rev_adj_id;
4072 
4073         l_rows_needing_rounding := round_rows_by_trx%ROWCOUNT;
4074 
4075         CLOSE round_rows_by_trx;
4076 
4077   /* Now update all the rows that require it */
4078 
4079   IF PG_DEBUG in ('Y', 'C') THEN
4080      arp_standard.debug('Rows that need rounding: ' || l_rows_needing_rounding);
4081   END IF;
4082 
4083   IF (l_rows_needing_rounding > 0) THEN
4084 
4085      /* DEBUG CODE +/
4086                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
4087                    arp_standard.debug(err || ' ' || t_line_id(err)|| '  ' ||
4088                                       t_account_class(err) ||
4089                      '  ' || t_round_amount(err) ||
4090                      ' ' || t_round_acctd(err) || ' ' ||
4091                      t_round_percent(err) );
4092                 END LOOP;
4093      /+ END DEBUG CODE */
4094 
4095      /* START - Main Loop */
4096      WHILE (l_phase < 5 and l_rows_needing_rounding - l_rows_rounded > 0)
4097      LOOP
4098 
4099         l_phase := l_phase + 1;
4100 
4101         IF PG_DEBUG in ('Y', 'C') THEN
4102             arp_standard.debug('  Pass = ' || l_phase);
4103         END IF;
4104 
4105         IF l_phase <=3
4106         THEN
4107           FORALL i IN t_line_id.FIRST .. t_line_id.LAST
4108            UPDATE ra_cust_trx_line_gl_dist
4109            SET    amount = amount + t_round_amount(i),
4113                   last_update_date = sysdate
4110                   percent = percent + t_round_percent(i),
4111                   acctd_amount = acctd_amount + t_round_acctd(i),
4112                   last_updated_by = arp_global.last_updated_by,
4114            WHERE  cust_trx_line_gl_dist_id in (
4115               /* SELECT GL_DIST_ID FOR EACH LINE THAT
4116                  REQUIRES ROUNDING */
4117               select MAX(g.cust_trx_line_gl_dist_id)
4118               from   ra_cust_trx_line_gl_dist g,
4119                      ra_cust_trx_line_gl_dist gmax,
4120                      ra_customer_trx_lines tl
4121               where  g.customer_trx_line_id = t_line_id(i)
4122               and    tl.customer_trx_line_id = g.customer_trx_line_id
4123               and    g.account_class = t_account_class(i)
4124               and    g.account_set_flag = 'N'
4125                      /* ONLY USE UNPOSTED ROWS */
4126               and    g.posting_control_id = -3
4127                      /* ONLY CONSIDERS NON-REC_OFFSET ROWS */
4128               and    g.rec_offset_flag IS NULL
4129                      /* only a specific rev_adj */
4130               and    g.revenue_adjustment_id = t_rev_adj_id(i)
4131                      /* FORCES USE OF ROW IN LAST PERIOD */
4132               and    g.gl_date = (
4133                          select max(gl_date)
4134                          from ra_cust_trx_line_gl_dist gdmax
4135                          where gdmax.customer_trx_line_id = g.customer_trx_line_id
4136                          and   gdmax.account_class = g.account_class
4137                          and   nvl(gdmax.rec_offset_flag, '~') =
4138                                          nvl(g.rec_offset_flag, '~')
4139                          and   gdmax.account_set_flag = 'N'
4140                          and   gdmax.posting_control_id = -3
4141                          and   gdmax.revenue_adjustment_id = t_rev_adj_id(i))
4142               and    gmax.customer_trx_line_id = g.customer_trx_line_id
4143               and    gmax.account_class = g.account_class
4144               and    gmax.account_set_flag = 'N'
4145               and    nvl(gmax.rec_offset_flag, '~') = nvl(g.rec_offset_flag, '~')
4146               and    gmax.gl_date = g.gl_date
4147                      /* ONLY RAM DISTRIBUTIONS */
4148               and    g.revenue_adjustment_id = gmax.revenue_adjustment_id
4149                      /* USE DISTS THAT MATCH SIGN OF LINE FIRST,
4150                         THEN OTHERS (ZERO, NEGATIVE). */
4151               and    (SIGN(g.amount) = SIGN(tl.revenue_amount) *
4152                                    DECODE(g.account_class, 'REV', 1,
4153                                       DECODE(g.rec_offset_flag, 'Y', 1, -1)) *
4154                                    DECODE(l_phase, 1, 1, 2, -1, 0))
4155                       /* SKIP UPDATE IF SIGNS AR OPPOSITE */
4156               and   (sign(g.amount + t_round_amount(i)) =
4157                      sign(g.acctd_amount + t_round_acctd(i)) or
4158                      sign(g.amount + t_round_amount(i)) = 0)
4159               having
4160                      /* USE LINE WITH LARGEST ABS(AMOUNT) */
4161                      g.amount = decode(sign(g.amount), -1, MIN(gmax.amount),
4162                                                         1, MAX(gmax.amount),
4163                                                         0)
4164               group by g.amount
4165               /* END OF GL_DIST_ID SELECT */
4166               );
4167         ELSE
4168            /* 6325023 - added 4th phase to handle SLA issues where
4169               entered and acctd_amount dists have opposite signs */
4170            /* 6473284 - Added 5th phase to extend fix for 6325023 to
4171                cover some odd corner cases.
4172 
4173               In discussing these phases, we are now focused on
4174               the signs of the amount and acctd corrections only.  If
4175               Either is zero or they are same sign, then we update the
4176               existing dists (phase 1-3), however, if the corrections force
4177               the resulting amount or acctd to be a different sign, then
4178               phase 4 and 5 may each insert additional distributions.
4179 
4180               Phase 4 inserts a new distribution if the signs become
4181               opposites after rounding.  Phase 5 splits entered and
4182               acctd when the amounts themselves are opposite signs
4183 
4184               Based on bug 6473284, I'm going to coin a new phrase..
4185               cases where the rounding is pennies is now called
4186               near-zero rounding.  Phases 4 and 5 are specific to
4187               cases where the rounding amount is near-zero (pennies)
4188               and the effect of that rounding makes the distributions
4189               change signs unpredictably.   This is just FYI   */
4190 
4191            FORALL i in t_line_id.first .. t_line_id.last
4192             INSERT INTO RA_CUST_TRX_LINE_GL_DIST
4193               (CUST_TRX_LINE_GL_DIST_ID,
4194                CREATED_BY,
4195                CREATION_DATE,
4196                LAST_UPDATED_BY,
4197                LAST_UPDATE_DATE,
4198                LAST_UPDATE_LOGIN,
4199                PROGRAM_APPLICATION_ID,
4200                PROGRAM_ID,
4201                PROGRAM_UPDATE_DATE,
4202                POSTING_CONTROL_ID,
4203                SET_OF_BOOKS_ID,
4204                CUSTOMER_TRX_LINE_ID,
4205                CUSTOMER_TRX_ID,
4206                ACCOUNT_CLASS,
4207                CODE_COMBINATION_ID,
4208                AMOUNT,
4209                ACCTD_AMOUNT,
4210                PERCENT,
4211                GL_DATE,
4212                ORIGINAL_GL_DATE,
4216                ATTRIBUTE1,
4213                ACCOUNT_SET_FLAG,
4214                COMMENTS,
4215                ATTRIBUTE_CATEGORY,
4217                ATTRIBUTE2,
4218                ATTRIBUTE3,
4219                ATTRIBUTE4,
4220                ATTRIBUTE5,
4221                ATTRIBUTE6,
4222                ATTRIBUTE7,
4223                ATTRIBUTE8,
4224                ATTRIBUTE9,
4225                ATTRIBUTE10,
4226                ATTRIBUTE11,
4227                ATTRIBUTE12,
4228                ATTRIBUTE13,
4229                ATTRIBUTE14,
4230                ATTRIBUTE15,
4231                LATEST_REC_FLAG,
4232                USSGL_TRANSACTION_CODE,
4233                REC_OFFSET_FLAG,
4234                USER_GENERATED_FLAG,
4235                ORG_ID,
4236                REQUEST_ID,
4237                CUST_TRX_LINE_SALESREP_ID,
4238                REVENUE_ADJUSTMENT_ID,
4239                EVENT_ID,
4240                ROUNDING_CORRECTION_FLAG
4241               )
4242         SELECT
4243             RA_CUST_TRX_LINE_GL_DIST_S.NEXTVAL,
4244             CREATED_BY,
4245             CREATION_DATE,
4246             LAST_UPDATED_BY,
4247             LAST_UPDATE_DATE,
4248             LAST_UPDATE_LOGIN,
4249             PROGRAM_APPLICATION_ID,
4250             PROGRAM_ID,
4251             PROGRAM_UPDATE_DATE,
4252             -3,
4253             SET_OF_BOOKS_ID,
4254             CUSTOMER_TRX_LINE_ID,
4255             CUSTOMER_TRX_ID,
4256             ACCOUNT_CLASS,
4257             CODE_COMBINATION_ID,
4258             DECODE(l_phase, 4, t_round_amount(i), 0),
4259             DECODE(l_phase, 4,
4260               DECODE(SIGN(t_round_amount(i)),0,t_round_acctd(i),
4261                    ABS(t_round_acctd(i)) * SIGN(t_round_amount(i))),
4262               t_round_acctd(i) * 2),
4263             DECODE(l_phase, 4, t_round_percent(i), 0),
4264             GL_DATE,
4265             ORIGINAL_GL_DATE,
4266             ACCOUNT_SET_FLAG,
4267             'PHASE ' || l_phase || ':  Rounding correction derived from ' ||
4268                cust_trx_line_gl_dist_id,
4269             ATTRIBUTE_CATEGORY,
4270             ATTRIBUTE1,
4271             ATTRIBUTE2,
4272             ATTRIBUTE3,
4273             ATTRIBUTE4,
4274             ATTRIBUTE5,
4275             ATTRIBUTE6,
4276             ATTRIBUTE7,
4277             ATTRIBUTE8,
4278             ATTRIBUTE9,
4279             ATTRIBUTE10,
4280             ATTRIBUTE11,
4281             ATTRIBUTE12,
4282             ATTRIBUTE13,
4283             ATTRIBUTE14,
4284             ATTRIBUTE15,
4285             LATEST_REC_FLAG,
4286             USSGL_TRANSACTION_CODE,
4287             REC_OFFSET_FLAG,
4288             USER_GENERATED_FLAG,
4289             ORG_ID,
4290             REQUEST_ID,
4291             CUST_TRX_LINE_SALESREP_ID,
4292             REVENUE_ADJUSTMENT_ID,
4293             EVENT_ID,
4294             'Y'
4295         FROM  RA_CUST_TRX_LINE_GL_DIST_ALL
4296         WHERE CUST_TRX_LINE_GL_DIST_ID IN (
4297               /* SELECT GL_DIST_ID FOR EACH LINE THAT
4298                  REQUIRES ROUNDING */
4299               select
4300                 to_number(substr(max(
4301                        to_char(g.gl_date,'YYYYMMDD') ||
4302                        decode(sign(g.amount *
4303                                  DECODE(g.account_class, 'REV', 1,
4304                                    DECODE(g.rec_offset_flag, 'Y', 1, -1))),
4305                               sign(tl.revenue_amount), '3',
4306                            sign(tl.revenue_amount * -1), '2', '1') ||
4307                        ltrim(to_char(abs(g.amount),'099999999999999.00')) ||
4308                        ltrim(to_char(g.cust_trx_line_gl_dist_id,
4309                                           '0999999999999999999999'))),28))
4310               from   ra_cust_trx_line_gl_dist g,
4311                      ra_customer_trx_lines tl
4312               where  g.customer_trx_line_id = t_line_id(i)
4313               and    tl.customer_trx_line_id = g.customer_trx_line_id
4314               and    g.account_class = t_account_class(i)
4315               and    g.account_set_flag = 'N'
4316                      /* ONLY USE UNPOSTED ROWS */
4317               and    g.posting_control_id = -3
4318                      /* REVENUE ADJUSTMENTS DO NOT AFFECT REC OFFSET ROWS */
4319               and    g.rec_offset_flag IS NULL
4320                      /* ONLY ROUND RAM DISTRIBUTIONS */
4321               and    g.revenue_adjustment_id = t_rev_adj_id(i)
4322               /* END OF GL_DIST_ID SELECT */
4323               );
4324 
4325         END IF;
4326 
4327        l_rows_rounded_this_pass := 0;
4328 
4329        /* START - Cleanup loop */
4330        FOR upd in t_line_id.FIRST .. t_line_id.LAST LOOP
4331 
4332           IF(SQL%BULK_ROWCOUNT(upd) = 1)
4333           THEN
4334 
4335           /* This piece of code determines that 1 row was updated
4336              for each invoice line and account class.  Once the
4337              row is updated, we need to remove it from further
4338              consideration.  To do that, we change the line_id
4339              to line_id * -1 (a row that should never exist)
4340              and this prevents it from being processed in
4341              subsequent passes.
4342 
4343              Incidentally, I tried to just delete the
4344              processed rows - but this caused subsequent
4345              passes to fail with ORA errors due to missing
4346              plsql table rows.  The bulk update requires
4347              a continuous list in sequential order and, by deleting
4348              rows from the table, we cause the update to fail.
4349           */
4350 
4351 
4352               IF PG_DEBUG in ('Y', 'C') THEN
4353                  arp_standard.debug('  Target: ' || t_line_id(upd) ||
4354                                 '  ' || t_account_class(upd) ||
4355                                 '  ' || t_round_amount(upd) ||
4356                                 '  ' || t_round_acctd(upd) ||
4357                                 ' ' || t_round_percent(upd) ||
4358                                 ' ' || SQL%BULK_ROWCOUNT(upd));
4359               END IF;
4360 
4361               IF l_phase = 4
4362               THEN
4363                  /* extra checks to see if we need last phase */
4364                  IF t_round_amount(upd) = 0
4365                     OR  t_round_acctd(upd) = 0
4366                     OR  SIGN(t_round_amount(upd)) = SIGN(t_round_acctd(upd))
4367                  THEN
4368                     /* This phase inserted complete dists
4369                        so no need to insert another dist */
4370                     l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
4371                     t_line_id(upd) := -1 * t_line_id(upd);
4372                  ELSE
4373                     /* Do not change the line_id or increment.. this
4374                         forces the last phase and an insert of
4375                         a dist with amount=0 and acctd_amount=<correction * 2>
4376                     */
4377                     NULL;
4378                  END IF;
4379               ELSE
4380                  /* previous behavior */
4381                  l_rows_rounded_this_pass := l_rows_rounded_this_pass + 1;
4382                  /* make line_id negative so it causes no further updates */
4383                  t_line_id(upd) := -1 * t_line_id(upd);
4384               END IF;
4385 
4386           END IF;
4387 
4388           IF(SQL%BULK_ROWCOUNT(upd) > 1)
4389           THEN
4390              /* Failure condition 1
4391                 This section of code executes only when more than
4392                 one line is updated for a given customer_trx_line_id
4393                 and account_class.  That would mean that the rounding
4394                 logic was unable to identify a single line for update
4395                 and rounding would then raise an error to roll back
4396                 any corrections or calculations for this transaction.
4397 
4398                 Revenue recognition has been modified to roll back
4399                 transactions that fail and to document the lines
4400                 that have problems.  */
4401 
4402              IF PG_DEBUG in ('Y', 'C')
4403              THEN
4404 
4405                 FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
4406                    arp_standard.debug(t_line_id(err)|| '  ' ||
4407                                       t_account_class(err) ||
4408                      '  ' || t_round_amount(err) ||
4409                      ' ' || t_round_acctd(err) || ' ' ||
4410                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
4411                 END LOOP;
4412 
4413              END IF;
4414 
4415              RETURN(iFALSE);
4416 
4417           END IF;
4418 
4419        END LOOP; /* END - Cleanup loop */
4420 
4421        IF PG_DEBUG in ('Y', 'C') THEN
4422           arp_standard.debug('    Rows rounded (this pass) : ' || l_rows_rounded_this_pass);
4423        END IF;
4424 
4425        l_rows_rounded := l_rows_rounded + l_rows_rounded_this_pass;
4426 
4427      END LOOP;  /* END - Main processing loop */
4428 
4432              In this situation, the total number of distributions corrected
4429        IF (l_rows_needing_rounding <> l_rows_rounded) THEN
4430 
4431           /* Failure condition 2
4433              does not match the number expected.  Because of condition 1
4434              handled above, this would only occur if we were unable to
4435              locate any rows to assess rounding corrections to for
4436              one or more invoice lines.  Such situations highlight
4437              shortcomings in this logic that must be investigated
4438              and corrected.
4439           */
4440 
4441           IF PG_DEBUG in ('Y', 'C') THEN
4442              arp_standard.debug('Mismatch between lines found and lines updated [see below]');
4443              arp_standard.debug('  Rows targeted: ' || l_rows_needing_rounding);
4444              arp_standard.debug('  Rows rounded : ' || l_rows_rounded);
4445 
4446              FOR err in t_line_id.FIRST .. t_line_id.LAST LOOP
4447 
4448                  arp_standard.debug(t_line_id(err) || '  ' || t_account_class(err) ||
4449                      '  ' || t_round_amount(err) || ' ' || t_round_acctd(err) || ' ' ||
4450                      t_round_percent(err) || '   ' || SQL%BULK_ROWCOUNT(err));
4451 
4452              END LOOP;
4453 
4454           END IF;
4455 
4456           RETURN(iFALSE);
4457        END IF;
4458 
4459        IF PG_DEBUG in ('Y', 'C') THEN
4460           arp_standard.debug('Total number of rows updated:  ' || l_rows_rounded);
4461        END IF;
4462 
4463   /* MRC Processing */
4464   IF PG_DEBUG in ('Y', 'C') THEN
4465      arp_standard.debug('doing rounding for MRC if necessary');
4466   END IF;
4467 
4468   /* This call to the MRC wrapper will eventually call a clone of this
4469      routine that was designed to round MRC gld table data.  The MRC
4470      call like the primary sob one utilizes the amounts and line_ids
4471      from ar_line_rev_adj_gt (global temporary table).
4472 
4473      Note that mrc_correct_rounding verifies that MRC is enabled before
4474      doing anything */
4475   ar_mrc_engine2.mrc_correct_rounding(
4476                    'CORRECT_REV_ADJ_BY_LINE',
4477                    NULL,    -- request_id
4478                    NULL,    -- customer_trx_id
4479                    NULL,    -- customer trx line id
4480                    NULL,
4481          	   NULL,    -- concat_segs
4482                    NULL,    -- balanced round_ccid
4483                    NULL,
4484                    NULL     -- period_set_name
4485                   );
4486   END IF;
4487 
4488   IF PG_DEBUG in ('Y', 'C') THEN
4489      arp_standard.debug('arp_rounding.correct_rev_adj_by_line()-');
4490   END IF;
4491 
4492   RETURN(iTRUE);
4493 END correct_rev_adj_by_line;
4494 
4495 /*-------------------------------------------------------------------------+
4496  | PRIVATE FUNCTION                                                        |
4497  | correct_line_level_rounding                                             |
4498  |                                                                         |
4499  | DESCRIPTION                                                             |
4500  | This function calls functions to correct rounding errors in             |
4501  | ra_cust_trx_line_gl_dist.                                               |
4502  |                                                                         |
4503  | REQUIRES                                                                |
4504  |   P_CUSTOMER_TRX_ID                                                     |
4505  |                                                                         |
4506  | RETURNS                                                                 |
4507  |   TRUE  if no errors occur                                              |
4508  |   FALSE otherwise.                                                      |
4509  |                                                                         |
4510  | NOTES                                                                   |
4511  |                                                                         |
4512  | EXAMPLE                                                                 |
4513  |                                                                         |
4514  | MODIFICATION HISTORY                                                    |
4515  |                                                                         |
4516  +-------------------------------------------------------------------------*/
4517 FUNCTION do_line_level_rounding(
4518                  P_REQUEST_ID            IN NUMBER,
4519                  P_CUSTOMER_TRX_ID       IN NUMBER,
4520                  P_CUSTOMER_TRX_LINE_ID  IN NUMBER,
4521                  P_ROWS_PROCESSED        IN OUT NOCOPY NUMBER,
4522                  P_ERROR_MESSAGE            OUT NOCOPY VARCHAR2,
4523                  P_BASE_PRECISION        IN NUMBER,
4524                  P_BASE_MIN_ACCOUNTABLE_UNIT IN NUMBER,
4525                  P_PERIOD_SET_NAME       IN OUT NOCOPY VARCHAR2,
4526                  P_CHECK_RULES_FLAG      IN VARCHAR2,
4527                  P_TRX_CLASS_TO_PROCESS  IN VARCHAR2,
4528                  P_FIX_REC_OFFSET        IN VARCHAR2 DEFAULT 'Y')
4529                  RETURN NUMBER IS
4530 
4531 begin
4532 
4533   IF PG_DEBUG in ('Y', 'C') THEN
4534      arp_standard.debug('arp_rounding.do_line_level_rounding()+ ' ||
4535                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4536   END IF;
4537 
4538     /*--------------------------------------------------------------+
4539      |  Correct each type of rounding error. Each function corrects |
4543     /*--------------------------------------------------------------+
4540      |  a different kind of error.                                  |
4541      +--------------------------------------------------------------*/
4542 
4544      |  Correct each type of rounding error. Each function corrects |
4545      |  a different kind of error.                                  |
4546      +--------------------------------------------------------------*/
4547 
4548    if ( correct_receivables_records( P_REQUEST_ID,
4549                                      P_CUSTOMER_TRX_ID,
4550                                      P_CUSTOMER_TRX_LINE_ID,
4551                                      P_ROWS_PROCESSED,
4552                                      P_ERROR_MESSAGE,
4553                                      P_BASE_PRECISION,
4554                                      P_BASE_MIN_ACCOUNTABLE_UNIT,
4555                                      P_TRX_CLASS_TO_PROCESS) = iFALSE)
4556    then return(iFALSE);
4557    end If;
4558 
4559 
4560    if ( correct_nonrule_line_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    if ( correct_rule_records_by_line( P_REQUEST_ID,
4572                               P_CUSTOMER_TRX_ID,
4573                               P_ROWS_PROCESSED,
4574                               P_ERROR_MESSAGE,
4575                               P_BASE_PRECISION,
4576                               P_BASE_MIN_ACCOUNTABLE_UNIT,
4577                               P_TRX_CLASS_TO_PROCESS,
4578                               P_CHECK_RULES_FLAG,
4579                               P_PERIOD_SET_NAME,
4580                               P_FIX_REC_OFFSET) = iFALSE)
4581    then return(iFALSE);
4582    end If;
4583 
4584    correct_suspense(p_customer_trx_id);
4585 
4586    IF PG_DEBUG in ('Y', 'C') THEN
4587       arp_standard.debug( 'arp_rounding.do_line_level_rounding()- ' ||
4588                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4589    END IF;
4590 
4591    return(iTRUE);
4592 
4593 end do_line_level_rounding;
4594 
4595 
4596 /*-------------------------------------------------------------------------+
4597  | PRIVATE FUNCTION                                                        |
4598  | replace_balancing_segment                                               |
4599  |                                                                         |
4600  | DESCRIPTION                                                             |
4601  |                                                                         |
4602  | This function accepts the REC and the ROUND code_combination_id,        |
4603  | replaces balancing segement of the ROUND accounting combination with    |
4604  | the REC segement and returns the new code_combination_id.               |
4605  |                                                                         |
4606  | REQUIRES                                                                |
4607  |                                                                         |
4608  | RETURNS                                                                 |
4609  |   TRUE  if no errors occur                                              |
4610  |   FALSE otherwise.                                                      |
4611  |                                                                         |
4612  | NOTES                                                                   |
4613  |                                                                         |
4614  | EXAMPLE                                                                 |
4615  |                                                                         |
4616  | MODIFICATION HISTORY                                                    |
4617  |      Satheesh Nambiar - 01/18/00                                        |
4618  |                         Bug 1152919. Added error_message as out NOCOPY         |
4619  |                         parameter to this private function              |
4620  +-------------------------------------------------------------------------*/
4621 
4622 FUNCTION replace_balancing_segment( original_ccid IN NUMBER,
4623                                     balancing_ccid IN NUMBER,
4624                                     return_ccid   OUT NOCOPY NUMBER,
4625                                     concat_segs   OUT NOCOPY VARCHAR2,
4626                                     error_message OUT NOCOPY VARCHAR2)
4627 RETURN NUMBER IS
4628 
4629 --concat_segs varchar2(240);
4630 concat_ids varchar2(2000);
4631 concat_descrs varchar2(2000);
4632 
4633 begin
4634 
4635    IF PG_DEBUG in ('Y', 'C') THEN
4636       arp_standard.debug( 'arp_rounding.replace_balancing_segment()+ ' ||
4637                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4638    END IF;
4639 
4640    if not AR_FLEXBUILDER_WF_PKG.SUBSTITUTE_BALANCING_SEGMENT(
4641                           arp_global.chart_of_accounts_id,
4642                           original_ccid,
4643                           balancing_ccid,
4644                           return_ccid,
4645                           concat_segs,
4646                           concat_ids,
4647                           concat_descrs,
4651       IF PG_DEBUG in ('Y', 'C') THEN
4648                           error_message )
4649    then
4650 
4652          arp_standard.debug('EXCEPTION:  substitute_balancing_segment failed ' ||
4653                            return_ccid);
4654       END IF;
4655       return(iFALSE);
4656    end if;
4657 
4658    IF PG_DEBUG in ('Y', 'C') THEN
4659       arp_standard.debug(' original_ccid: ' || original_ccid ||
4660                             ' balancing_ccid: ' || balancing_ccid ||
4661                             ' return_ccid: ' || return_ccid ||
4662                             ' concat_segs: ' || concat_segs
4663                       );
4664       arp_standard.debug( 'arp_rounding.replace_balancing_segment()- ' ||
4665                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4666    END IF;
4667 
4668    return(iTRUE);
4669 
4670 end replace_balancing_segment;
4671 
4672 /*-------------------------------------------------------------------------+
4673  | PRIVATE FUNCTION                                                        |
4674  | correct_header_level_rounding                                           |
4675  |                                                                         |
4676  | DESCRIPTION                                                             |
4677  | This function calls functions to correct rounding errors in             |
4678  | ra_cust_trx_line_gl_dist.                                               |
4679  |                                                                         |
4680  | REQUIRES                                                                |
4681  |   P_CUSTOMER_TRX_ID                                                     |
4682  |                                                                         |
4683  | RETURNS                                                                 |
4684  |   TRUE  if no errors occur                                              |
4685  |   FALSE otherwise.                                                      |
4686  |                                                                         |
4687  | NOTES                                                                   |
4688  |                                                                         |
4689  | EXAMPLE                                                                 |
4690  |                                                                         |
4691  | MODIFICATION HISTORY                                                    |
4692  |                                                                         |
4693  +-------------------------------------------------------------------------*/
4694 FUNCTION correct_header_level_rounding(
4695                  P_REQUEST_ID IN NUMBER,
4696                  P_CUSTOMER_TRX_ID           IN NUMBER,
4697                  P_CUSTOMER_TRX_LINE_ID      IN NUMBER,
4698                  P_ROWS_PROCESSED            IN OUT NOCOPY NUMBER,
4699                  P_ERROR_MESSAGE            OUT NOCOPY VARCHAR2,
4700                  P_BASE_PRECISION            IN NUMBER,
4701                  P_BASE_MIN_ACCOUNTABLE_UNIT IN NUMBER,
4702                  P_PERIOD_SET_NAME           IN OUT NOCOPY VARCHAR2,
4703                  P_CHECK_RULES_FLAG          IN VARCHAR2,
4704                  P_TRX_CLASS_TO_PROCESS      IN VARCHAR2,
4705                  P_REC_CODE_COMBINATION_ID   IN NUMBER,
4706                  P_TRX_HEADER_ROUND_CCID     IN NUMBER,
4707                  P_FIX_REC_OFFSET            IN VARCHAR2 DEFAULT 'Y')
4708 RETURN NUMBER IS
4709 
4710 balanced_round_ccid number;
4711 concat_segs varchar2(240);
4712 
4713 begin
4714 
4715   IF PG_DEBUG in ('Y', 'C') THEN
4716      arp_standard.debug('arp_rounding.correct_header_level_rounding()+ ' ||
4717                      to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4718   END IF;
4719 
4720     /*--------------------------------------------------------------+
4721      |  Correct each type of rounding error. Each function corrects |
4722      |  a different kind of error.                                  |
4723      +--------------------------------------------------------------*/
4724 
4725    if ( correct_receivables_header( P_REQUEST_ID,
4726                                     P_CUSTOMER_TRX_ID,
4727                                     P_CUSTOMER_TRX_LINE_ID,
4728                                     P_ROWS_PROCESSED,
4729                                     P_ERROR_MESSAGE,
4730                                     P_BASE_PRECISION,
4731                                     P_BASE_MIN_ACCOUNTABLE_UNIT,
4732                                     P_TRX_CLASS_TO_PROCESS) = iFALSE)
4733    then return(iFALSE);
4734    end If;
4735 
4736 
4737    if ( correct_nonrule_line_records( 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    if ( correct_rule_records_by_line( P_REQUEST_ID,
4749                               P_CUSTOMER_TRX_ID,
4750                               P_ROWS_PROCESSED,
4751                               P_ERROR_MESSAGE,
4752                               P_BASE_PRECISION,
4753                               P_BASE_MIN_ACCOUNTABLE_UNIT,
4757                               P_FIX_REC_OFFSET) = iFALSE)
4754                               P_TRX_CLASS_TO_PROCESS,
4755                               P_CHECK_RULES_FLAG,
4756                               P_PERIOD_SET_NAME,
4758    then return(iFALSE);
4759    end If;
4760 
4761    --Bug 954681 and 1158340: Call the replace_balancing_segment routine
4762    --only if the REC ccid is valid.
4763   IF P_REC_CODE_COMBINATION_ID  > -1  THEN
4764 
4765    if ( replace_balancing_segment( P_TRX_HEADER_ROUND_CCID,
4766                                    P_REC_CODE_COMBINATION_ID,
4767                                    balanced_round_ccid,
4768                                    CONCAT_SEGS ,
4769                                    P_ERROR_MESSAGE) = iFALSE)
4770    then
4771     return(iFALSE);
4772    end If;
4773   END IF;
4774 
4775    /*--------------------------------------------------------------+
4776     |  If the balanced_round_ccid is returned as -1 then           |
4777     |  it gets the value of p_trx_header_round_ccid which is valid |
4778     |  code combination id as opposed to -1                        |
4779     +--------------------------------------------------------------*/
4780    /* Bug 5707676. if P_REC_CODE_COMBINATION_ID is -1 then balanced_round_ccid will NOT be initialized. So put NVL in if clause */
4781 
4782    if ( nvl(balanced_round_ccid,-1) = -1)
4783 
4784    then
4785         balanced_round_ccid := P_TRX_HEADER_ROUND_CCID;
4786    end if;
4787 
4788    if ( correct_round_records( P_REQUEST_ID,
4789                                P_CUSTOMER_TRX_ID,
4790                                P_CUSTOMER_TRX_LINE_ID,
4791                                P_ROWS_PROCESSED,
4792                                P_ERROR_MESSAGE,
4793                                P_BASE_PRECISION,
4794                                P_BASE_MIN_ACCOUNTABLE_UNIT,
4795                                P_TRX_CLASS_TO_PROCESS,
4796                                CONCAT_SEGS,
4797                                BALANCED_ROUND_CCID) = iFALSE)
4798    then return(iFALSE);
4799    end If;
4800 
4801    IF PG_DEBUG in ('Y', 'C') THEN
4802       arp_standard.debug( 'arp_rounding.correct_header_level_rounding()- ' ||
4803                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
4804    END IF;
4805 
4806    return(iTRUE);
4807 
4808 end correct_header_level_rounding;
4809 
4810 PROCEDURE get_select_column_values(
4811         P_SELECT_SQL_C   IN INTEGER,
4812         P_SELECT_REC IN OUT NOCOPY SELECT_REC_TYPE ) IS
4813 BEGIN
4814 
4815     IF PG_DEBUG in ('Y', 'C') THEN
4816        arp_standard.debug( 'arp_rounding.get_select_column_values()+' );
4817     END IF;
4818 
4819     dbms_sql.column_value( p_select_sql_c, 1,
4820                            p_select_rec.rec_customer_trx_id);
4821     dbms_sql.column_value( p_select_sql_c, 2,
4822                            p_select_rec.rec_code_combination_id);
4823     dbms_sql.column_value( p_select_sql_c, 3,
4824                            p_select_rec.round_customer_trx_id);
4825 
4826     IF PG_DEBUG in ('Y', 'C') THEN
4827        arp_standard.debug( 'arp_rounding.get_select_column_values()-' );
4828     END IF;
4829 
4830 EXCEPTION
4831     WHEN OTHERS THEN
4832         IF PG_DEBUG in ('Y', 'C') THEN
4833            arp_standard.debug('EXCEPTION: arp_rounding.get_select_column_values()');
4834         END IF;
4835         RAISE;
4836 END get_select_column_values;
4837 
4838 PROCEDURE dump_select_rec( P_SELECT_REC IN SELECT_REC_TYPE ) IS
4839 BEGIN
4840 
4841     IF PG_DEBUG in ('Y', 'C') THEN
4842        arp_standard.debug( 'arp_rounding.dump_select_rec()+' );
4843        arp_standard.debug('  Dumping select record: ');
4844        arp_standard.debug('  rec_customer_trx_id=' ||
4845                  p_select_rec.rec_customer_trx_id);
4846        arp_standard.debug('  rec_code_combination_id=' ||
4847                  p_select_rec.rec_code_combination_id);
4848        arp_standard.debug('  round_customer_trx_id=' ||
4849                  p_select_rec.round_customer_trx_id);
4850        arp_standard.debug( 'arp_rounding.dump_select_rec()-' );
4851     END IF;
4852 
4853 EXCEPTION
4854     WHEN OTHERS THEN
4855        IF PG_DEBUG in ('Y', 'C') THEN
4856           arp_standard.debug( 'EXCEPTION: arp_rounding.dump_select_rec()' );
4857        END IF;
4858         RAISE;
4859 END dump_select_rec;
4860 
4861 
4862 PROCEDURE define_columns( P_SELECT_SQL_C IN INTEGER,
4863                           P_SELECT_REC IN SELECT_REC_TYPE) IS
4864 BEGIN
4865 
4866     arp_standard.debug( 'arp_rounding.define_columns()+' );
4867 
4868     ------------------------------------------------------------
4869     -- Define columns
4870     ------------------------------------------------------------
4871         arp_standard.debug( '  Defining columns for select_sql_c');
4872 
4873         dbms_sql.define_column( p_select_sql_c, 1,
4874                                 p_select_rec.rec_customer_trx_id );
4875         dbms_sql.define_column( p_select_sql_c, 2,
4876                                 p_select_rec.rec_code_combination_id );
4877         dbms_sql.define_column( p_select_sql_c, 3,
4878                                 p_select_rec.round_customer_trx_id );
4879 
4880     arp_standard.debug( 'arp_rounding.define_columns()-' );
4881 
4882 EXCEPTION
4883    WHEN OTHERS THEN
4884         arp_standard.debug( 'EXCEPTION: Error defining columns for select_sql_c' );
4885         RAISE;
4886 END;
4887 
4891                            P_CUSTOMER_TRX_ID IN INTEGER,
4888 
4889 PROCEDURE build_select_sql(
4890                            P_REQUEST_ID IN INTEGER,
4892                            P_SELECT_SQL_C IN OUT NOCOPY INTEGER  ) IS
4893 
4894     l_select_sql   VARCHAR2(1000);
4895     l_where_pred   VARCHAR2(500);
4896 
4897 BEGIN
4898 
4899     IF PG_DEBUG in ('Y', 'C') THEN
4900        arp_standard.debug( 'arp_rounding.build_select_sql()+' );
4901     END IF;
4902 
4903     ------------------------------------------------
4904     -- Construct where predicate
4905     ------------------------------------------------
4906 
4907     IF ( p_customer_trx_id IS NOT NULL ) THEN
4908         ----------------------------------------------------
4909         -- Passed customer_trx_id
4910         ----------------------------------------------------
4911 
4912         l_where_pred :=
4913 'AND rec.customer_trx_id = :p_customer_trx_id ';
4914     ELSE
4915 
4916         l_where_pred :=
4917 'AND rec.request_id = :p_request_id ';
4918 
4919     END IF;
4920 
4921     l_select_sql :=
4922 'select rec.customer_trx_id,
4923 rec.code_combination_id,
4924 round.customer_trx_id
4925 from
4926 ra_cust_trx_line_gl_dist rec,
4927 ra_cust_trx_line_gl_dist round
4928 where
4929 rec.customer_trx_id = round.customer_trx_id(+)
4930 and    rec.account_set_flag = round.account_set_flag(+)' ||
4931 l_where_pred  ||
4932 'and    rec.account_class = ''REC''
4933 and    rec.latest_rec_flag = ''Y''
4934 and    round.account_class(+) = ''ROUND''';
4935 
4936    IF PG_DEBUG in ('Y', 'C') THEN
4937       arp_standard.debug('select_sql =  ' ||
4938                        l_select_sql);
4939    END IF;
4940 
4941     ------------------------------------------------
4942     -- Parse sql stmts
4943     ------------------------------------------------
4944 
4945    BEGIN
4946         IF PG_DEBUG in ('Y', 'C') THEN
4947            arp_standard.debug('Parsing select stmt');
4948         END IF;
4949 
4950         p_select_sql_c := dbms_sql.open_cursor;
4951         dbms_sql.parse( p_select_sql_c, l_select_sql, dbms_sql.v7 );
4952 
4953         IF ( p_customer_trx_id IS NOT NULL ) THEN
4954             ----------------------------------------------------
4955             -- Passed customer_trx_id
4956             ----------------------------------------------------
4957             dbms_sql.bind_variable(p_select_sql_c, ':p_customer_trx_id', p_customer_trx_id);
4958 
4959         ELSE
4960 
4961             dbms_sql.bind_variable(p_select_sql_c, ':p_request_id', p_request_id);
4962 
4963         END IF;
4964 
4965     EXCEPTION
4966       WHEN OTHERS THEN
4967           IF PG_DEBUG in ('Y', 'C') THEN
4968              arp_standard.debug('build_select_sql: ' ||  'EXCEPTION: Error parsing select stmt' );
4969           END IF;
4970           RAISE;
4971     END;
4972 
4973     IF PG_DEBUG in ('Y', 'C') THEN
4974        arp_standard.debug( 'arp_rounding.build_select_sql()-' );
4975     END IF;
4976 
4977 
4978 EXCEPTION
4979     WHEN OTHERS THEN
4980         IF PG_DEBUG in ('Y', 'C') THEN
4981            arp_standard.debug( 'EXCEPTION: arp_rounding.build_select_sql()' );
4982         END IF;
4983 
4984         RAISE;
4985 END build_select_sql;
4986 /*-------------------------------------------------------------------------+
4987  | PRIVATE FUNCTION                                                        |
4988  | do_header_level_rounding                                                |
4989  |                                                                         |
4990  | DESCRIPTION                                                             |
4991  |   This function inserts a record of account_class = ROUND into          |
4992  |   ra_cust_trx_line_gl_dist table. If the transaction was created before |
4993  |   setting the header level rounding option On then this function will   |
4994  |   insert the round record only if there is no activity on it otherwise  |
4995  |   it will do the release 10 rounding (do_line_level_rounding).          |
4996  |   Also if arp_rounding is called from revenue recognition program then  |
4997  |   this function will not insert the ROUND record but revenue recognition|
4998  |   will insert it.                                                       |
4999  |                                                                         |
5000  | REQUIRES                                                                |
5001  |   P_REQUEST_ID, P_CUSTOMER_TRX_ID                                       |
5002  |                                                                         |
5003  | RETURNS                                                                 |
5004  |   TRUE  if no errors occur                                              |
5005  |   FALSE otherwise.                                                      |
5006  |                                                                         |
5007  | NOTES                                                                   |
5008  |                                                                         |
5009  | EXAMPLE                                                                 |
5010  |                                                                         |
5011  | MODIFICATION HISTORY                                                    |
5012  |                                                                         |
5013  +-------------------------------------------------------------------------*/
5014 
5015 FUNCTION do_header_level_rounding
5016                  ( P_REQUEST_ID                    IN NUMBER,
5017                    P_CUSTOMER_TRX_ID               IN NUMBER,
5018                    P_CUSTOMER_TRX_LINE_ID          IN NUMBER,
5019                    P_ROWS_PROCESSED            IN OUT NOCOPY NUMBER,
5020                    P_ERROR_MESSAGE                OUT NOCOPY VARCHAR2,
5021                    P_BASE_PRECISION                IN NUMBER,
5022                    P_BASE_MIN_ACCOUNTABLE_UNIT     IN VARCHAR2,
5023                    P_TRX_CLASS_TO_PROCESS          IN VARCHAR2,
5024                    P_PERIOD_SET_NAME           IN OUT NOCOPY VARCHAR2,
5025                    P_CHECK_RULES_FLAG              IN VARCHAR2,
5026                    P_TRX_HEADER_LEVEL_ROUNDING     IN VARCHAR2,
5027                    P_ACTIVITY_FLAG                 IN VARCHAR2,
5028                    P_TRX_HEADER_ROUND_CCID         IN NUMBER,
5029                    P_FIX_REC_OFFSET                IN VARCHAR2 DEFAULT 'Y'
5030                  )
5031 RETURN NUMBER IS
5032 
5033   l_select_rec              select_rec_type;
5034   l_null_rec       CONSTANT select_rec_type := l_select_rec;
5035   l_ignore                  INTEGER;
5036   l_request_id              INTEGER;
5037   l_customer_trx_id         INTEGER;
5038 
5039 begin
5040 
5041  /* bug 912501 : Added 'G' for the possible values of p_activity_flag */
5042    if (p_activity_flag = 'Y' OR p_activity_flag = 'G') OR (p_check_rules_flag = 'Y' )
5043    then
5044       NULL;
5045    else
5046       if ( insert_round_records( P_REQUEST_ID,
5047                                  P_CUSTOMER_TRX_ID,
5048                                  P_ROWS_PROCESSED,
5049                                  P_ERROR_MESSAGE,
5050                                  P_BASE_PRECISION,
5051                                  P_BASE_MIN_ACCOUNTABLE_UNIT,
5052                                  P_TRX_CLASS_TO_PROCESS,
5053                                  P_TRX_HEADER_ROUND_CCID) = iFALSE)
5054       then return(iFALSE);
5055       end if;
5056    end if;
5057 
5058 
5059    -----------------------------------------------------------------------
5060    -- Create dynamic sql
5061    -----------------------------------------------------------------------
5062    IF PG_DEBUG in ('Y', 'C') THEN
5063      arp_standard.debug('  Creating dynamic sql');
5064   END IF;
5065 
5066    build_select_sql( P_REQUEST_ID,
5067                      P_CUSTOMER_TRX_ID,
5068                      SELECT_SQL_C);
5069 
5070    -----------------------------------------------------------
5071    -- Define columns
5072    -----------------------------------------------------------
5073    define_columns( select_sql_c, l_select_rec );
5074 
5075    ---------------------------------------------------------------
5076    -- Execute sql
5077    ---------------------------------------------------------------
5078    IF PG_DEBUG in ('Y', 'C') THEN
5079       arp_standard.debug('  Executing select sql' );
5080    END IF;
5081 
5082    BEGIN
5083        l_ignore := dbms_sql.execute( select_sql_c );
5084 
5085    EXCEPTION
5086       WHEN OTHERS THEN
5087             IF PG_DEBUG in ('Y', 'C') THEN
5088                arp_standard.debug('EXCEPTION: Error executing select sql' );
5089             END IF;
5090             RAISE;
5091    END;
5092 
5093    --------------------------------------------------------------
5094    -- Fetch rows
5095    --------------------------------------------------------------
5096    IF PG_DEBUG in ('Y', 'C') THEN
5100    begin
5097       arp_standard.debug('  Fetching select stmt');
5098    END IF;
5099 
5101       loop
5102          if (dbms_sql.fetch_rows( select_sql_c ) > 0)
5103          then
5104 
5105             IF PG_DEBUG in ('Y', 'C') THEN
5106                arp_standard.debug('  fetched a row' );
5107             END IF;
5108             l_select_rec := l_null_rec;
5109             ------------------------------------------------------
5110             -- Get column values
5111             ------------------------------------------------------
5112             get_select_column_values( select_sql_c, l_select_rec );
5113 
5114             dump_select_rec( l_select_rec );
5115          else
5116             IF PG_DEBUG in ('Y', 'C') THEN
5117                arp_standard.debug(   '  Done fetching');
5118             END IF;
5119             EXIT;
5120          end if;
5121 
5122        -- further processing.
5123 
5124          l_customer_trx_id := l_select_rec.rec_customer_trx_id;
5125 
5126          IF PG_DEBUG in ('Y', 'C') THEN
5127             arp_standard.debug(  'rec_customer_trx_id: '||  l_customer_trx_id);
5128          END IF;
5129 
5130          if (l_select_rec.round_customer_trx_id is null)
5131          then
5132             -- ROUND record does not exist for this transaction
5133             -- This means the transaction was created before
5134             -- setting TRX_HEADER_LEVEL_ROUNDING ON
5135             -- Round the transaction with release 10 method
5136 
5137             if ( do_line_level_rounding( l_REQUEST_ID,
5138                                          l_CUSTOMER_TRX_ID,
5139                                          P_CUSTOMER_TRX_LINE_ID,
5140                                          P_ROWS_PROCESSED,
5141                                          P_ERROR_MESSAGE,
5142                                          P_BASE_PRECISION,
5143                                          P_BASE_MIN_ACCOUNTABLE_UNIT,
5144                                          P_PERIOD_SET_NAME,
5145                                          P_CHECK_RULES_FLAG,
5146                                          P_TRX_CLASS_TO_PROCESS,
5147                                          P_FIX_REC_OFFSET) = iFALSE)
5148             then return(iFALSE);
5149             end If;
5150          else
5151             if ( correct_header_level_rounding( l_REQUEST_ID,
5152                                                 l_CUSTOMER_TRX_ID,
5153                                                 P_CUSTOMER_TRX_LINE_ID,
5154                                                 P_ROWS_PROCESSED,
5155                                                 P_ERROR_MESSAGE,
5156                                                 P_BASE_PRECISION,
5157                                                 P_BASE_MIN_ACCOUNTABLE_UNIT,
5158                                                 P_PERIOD_SET_NAME,
5159                                                 P_CHECK_RULES_FLAG,
5160                                                 P_TRX_CLASS_TO_PROCESS,
5161                                         l_select_rec.rec_code_combination_id,
5162                                         P_TRX_HEADER_ROUND_CCID) = iFALSE)
5163             then return(iFALSE);
5164             end If;
5165          end if;
5166       end loop;
5167 --Bug 1777081:Close the cursor to avoid the maximum cursor exceeding error.
5168 
5169       dbms_sql.close_cursor(select_sql_c);
5170    end;
5171 
5172    IF PG_DEBUG in ('Y', 'C') THEN
5173       arp_standard.debug( 'arp_rounding.do_header_level_rounding()- ' ||
5174                       to_char(sysdate, 'DD-MON-YY HH:MI:SS'));
5175    END IF;
5176 
5177    return(iTRUE);
5178 
5179 end do_header_level_rounding;
5180 
5181 
5182 /*-------------------------------------------------------------------------+
5183  | PUBLIC FUNCTION                                                         |
5184  |   correct_dist_rounding_errors()                                        |
5185  |                                                                         |
5186  | DESCRIPTION                                                             |
5187  |   This function corrects all rounding errors in the                     |
5188  |   ra_cust_trx_line_gl_dist table.                                       |
5189  |                                                                         |
5190  | REQUIRES                                                                |
5191  |   P_REQUEST_ID, P_CUSTOMER_TRX_ID or P_CUSTOMER_TRX_LINE_ID             |
5192  |   If header level rounding is enforced then requires either of          |
5193  |   P_REQUEST_ID, P_CUSTOMER_TRX_ID.                                      |
5194  |                                                                         |
5195  | RETURNS                                                                 |
5196  |   TRUE  if no errors occur                                              |
5197  |   FALSE otherwise.                                                      |
5198  |                                                                         |
5199  | NOTES                                                                   |
5200  |                                                                         |
5201  | EXAMPLE                                                                 |
5202  |                                                                         |
5203  | MODIFICATION HISTORY                                                    |
5204  |   03-AUG-2002  MRAYMOND   Added p_fix_rec_offset parameter to indicate
5205  |                            when to run the fix logic.
5206  +-------------------------------------------------------------------------*/
5207 
5208 FUNCTION correct_dist_rounding_errors
5209                  ( P_REQUEST_ID                    IN NUMBER,
5210                    P_CUSTOMER_TRX_ID               IN NUMBER,
5211                    P_CUSTOMER_TRX_LINE_ID          IN NUMBER,
5212                    P_ROWS_PROCESSED                IN OUT NOCOPY NUMBER,
5216                    P_TRX_CLASS_TO_PROCESS          IN VARCHAR2  DEFAULT 'ALL',
5213                    P_ERROR_MESSAGE                 OUT NOCOPY VARCHAR2,
5214                    P_BASE_PRECISION                IN NUMBER,
5215                    P_BASE_MIN_ACCOUNTABLE_UNIT     IN VARCHAR2,
5217                    P_CHECK_RULES_FLAG              IN VARCHAR2  DEFAULT 'N',
5218                    P_DEBUG_MODE                    IN VARCHAR2,
5219                    P_TRX_HEADER_LEVEL_ROUNDING     IN VARCHAR2  DEFAULT 'N',
5220                    P_ACTIVITY_FLAG                 IN VARCHAR2  DEFAULT 'N',
5221                    P_FIX_REC_OFFSET                IN VARCHAR2  DEFAULT 'Y'
5222                  )
5223 	RETURN NUMBER IS
5224 
5225   base_precision            NUMBER;
5226   base_min_accountable_unit NUMBER;
5227   trx_class_to_process      VARCHAR2(15);
5228   check_rules_flag          VARCHAR2(2);
5229   period_set_name           VARCHAR2(15);
5230   trx_header_round_ccid     number;
5231   l_select_rec              select_rec_type;
5232   l_null_rec       CONSTANT select_rec_type := l_select_rec;
5233   l_ignore                  INTEGER;
5234   activity_flag             VARCHAR2(1);
5235 
5236 
5237 BEGIN
5238 
5239   /*-------------------------------------------------------+
5240    |  Set a savepoint to rollback to if the function fails |
5241    +-------------------------------------------------------*/
5242 
5243    SAVEPOINT ARPLBCRE_1;
5244 
5245    IF ( do_setup(
5246                  P_REQUEST_ID,
5247                  P_CUSTOMER_TRX_ID,
5248                  P_CUSTOMER_TRX_LINE_ID,
5249                  P_BASE_PRECISION,
5250                  P_BASE_MIN_ACCOUNTABLE_UNIT,
5251                  P_TRX_CLASS_TO_PROCESS,
5252                  P_CHECK_RULES_FLAG,
5253                  P_DEBUG_MODE,
5254                  BASE_PRECISION,
5255                  BASE_MIN_ACCOUNTABLE_UNIT,
5256                  TRX_CLASS_TO_PROCESS,
5257                  CHECK_RULES_FLAG,
5258                  PERIOD_SET_NAME,
5259                  P_ROWS_PROCESSED,
5260                  P_ERROR_MESSAGE,
5261                  P_TRX_HEADER_LEVEL_ROUNDING,
5262                  P_ACTIVITY_FLAG,
5263                  ACTIVITY_FLAG,
5264                  TRX_HEADER_ROUND_CCID
5265                ) = iFALSE )
5266    THEN
5267        RETURN( iFALSE );
5268    END IF;
5269 
5270 
5271    /*----------------------------------------------+
5272     |  Print out NOCOPY the parameters in debug mode only |
5273     +----------------------------------------------*/
5274 
5275    IF PG_DEBUG in ('Y', 'C') THEN
5276       arp_standard.debug( 'arp_rounding.correct_dist_rounding_errors()+ ' ||
5277                       TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
5278       arp_standard.debug('  Request_id: ' || p_request_id ||
5279                      ' ctid: '|| p_customer_trx_id ||'  ctlid: '||
5280                      p_customer_trx_line_id || '  class: ' ||
5281                      trx_class_to_process || '  Rules: '||
5282                      check_rules_flag);
5283       arp_standard.debug(' Precision: ' || base_precision ||
5284                      '  MAU: ' || base_min_accountable_unit ||
5285                      '  Period Set: '|| period_set_name);
5286       arp_standard.debug('p_trx_header_level_rounding: ' ||
5287                      p_trx_header_level_rounding || ' p_activity_flag:' ||
5288                      p_activity_flag || ' trx_header_round_ccid:' ||
5289                      trx_header_round_ccid);
5290    END IF;
5291 
5292     /*--------------------------------------------------------------+
5293      |  Correct each type of rounding error. Each function corrects |
5294      |  a different kind of error.                                  |
5295      +--------------------------------------------------------------*/
5296 
5297 
5298    if (p_trx_header_level_rounding = 'Y')
5299    then
5300       if ( do_header_level_rounding( P_REQUEST_ID,
5301                                      P_CUSTOMER_TRX_ID,
5302                                      P_CUSTOMER_TRX_LINE_ID,
5303                                      P_ROWS_PROCESSED,
5304                                      P_ERROR_MESSAGE,
5305                                      BASE_PRECISION,
5306                                      BASE_MIN_ACCOUNTABLE_UNIT,
5307                                      TRX_CLASS_TO_PROCESS,
5308                                      PERIOD_SET_NAME,
5309                                      CHECK_RULES_FLAG,
5310                                      P_TRX_HEADER_LEVEL_ROUNDING,
5311                                      ACTIVITY_FLAG,
5312                                      TRX_HEADER_ROUND_CCID,
5313                                      P_FIX_REC_OFFSET) = iFALSE)
5314       then return(iFALSE);
5315       end if;
5316    else
5317       /* Do the release 10 rounding */
5318       if ( do_line_level_rounding( P_REQUEST_ID,
5319                                    P_CUSTOMER_TRX_ID,
5320                                    P_CUSTOMER_TRX_LINE_ID,
5321                                    P_ROWS_PROCESSED,
5322                                    P_ERROR_MESSAGE,
5323                                    BASE_PRECISION,
5324                                    BASE_MIN_ACCOUNTABLE_UNIT,
5325                                    PERIOD_SET_NAME,
5326                                    CHECK_RULES_FLAG,
5327                                    TRX_CLASS_TO_PROCESS,
5328                                    P_FIX_REC_OFFSET) = iFALSE)
5329       then return(iFALSE);
5330       end if;
5331    end if;
5332 
5333    IF PG_DEBUG in ('Y', 'C') THEN
5334       arp_standard.debug( 'arp_rounding.correct_dist_rounding_errors()- ' ||
5335                       TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
5336    END IF;
5337 
5338    RETURN( iTRUE );
5339 
5340   /*---------------------------------------------------------------------+
5344    +---------------------------------------------------------------------*/
5341    |  If any of the functions encounter an ORACLE error, that error is   |
5342    |  trapped here. The message is copied into the error_message         |
5343    |  parameter, and the function rolls back and returns FALSE.          |
5345 
5346 EXCEPTION
5347    WHEN OTHERS THEN
5348         p_error_message := SQLERRM;
5349 
5350         ROLLBACK TO SAVEPOINT ARPLBCRE_1;
5351 
5352         IF PG_DEBUG in ('Y', 'C') THEN
5353            arp_standard.debug( 'arp_rounding.correct_dist_rounding_errors()+ ' ||
5354                          TO_CHAR(sysdate, 'DD-MON-YY HH:MI:SS'));
5355         END IF;
5356 
5357         RETURN( iFALSE );
5358 
5359 
5360 END correct_dist_rounding_errors;
5361 
5362 /*-------------------------------------------------------------------------+
5363  | PUBLIC PROCEDURE                                                        |
5364  |   correct_scredit_rounding_errs()                                       |
5365  |                                                                         |
5366  | DESCRIPTION                                                             |
5367  |   This function corrects all rounding errors in the                     |
5368  |   ra_cust_trx_line_salesreps table.                                     |
5369  |                                                                         |
5370  | REQUIRES                                                                |
5371  |   P_CUSTOMER_TRX_ID							   |
5372  |                                                                         |
5373  | NOTES                                                                   |
5374  |                                                                         |
5375  | EXAMPLE                                                                 |
5376  |                                                                         |
5377  | MODIFICATION HISTORY                                                    |
5378  |   30-AUG-95  Charlie Tomberg       Created                              |
5379  |   03-OCT-03  M Raymond      Bug 3155664 - commented out nonrev scredit
5380  |                             rounding logic (it was ineffective)
5381  |                             and modified rev scredit logic to avoid
5382  |                             ORA-979 errors.
5383  +-------------------------------------------------------------------------*/
5384 
5385 PROCEDURE correct_scredit_rounding_errs( p_customer_trx_id   IN NUMBER,
5386                                          p_rows_processed   OUT NOCOPY NUMBER
5387                                          ) IS
5388 
5389   l_count number;
5390 
5391 BEGIN
5392 
5393   /*-------------------------------------------------------+
5394    |  Set a savepoint to rollback to if the function fails |
5395    +-------------------------------------------------------*/
5396 
5397    SAVEPOINT ARPLBCRE_2;
5398 
5399    arp_util.print_fcn_label( 'arp_rounding.correct_scredit_rounding_errs()+ ');
5400 
5401  /*-------------------------------------------------------------------------+
5402   |  Correct errors in the revenue_amount_split and revenue_percent_split   |
5403   |  columns:                                                               |
5404   |                                                                         |
5405   |    - Insure that the sum of the revenue percents equals 100 if the sum  |
5406   |      of the revenue amounts equals the line amount.                     |
5407   |    - Insure that the sum of revenue amounts equals the line amount if   |
5408   |      the sum of the revenue percents equals 100.                        |
5409   +-------------------------------------------------------------------------*/
5410 
5411    UPDATE ra_cust_trx_line_salesreps ctls
5412    SET     (
5413               ctls.revenue_amount_split,
5414               ctls.revenue_percent_split
5415            ) =
5416            (
5417              SELECT ctls.revenue_amount_split +
5418                     (
5419                        ctl1.extended_amount -
5420                        SUM(
5421                              NVL(ctls1.revenue_amount_split, 0)
5422                           )
5423                     ),
5424                     ctls.revenue_percent_split +
5425                     (
5426                        100 -
5427                        SUM(
5428                              NVL(ctls1.revenue_percent_split, 0)
5429                           )
5430                     )
5431              FROM     ra_customer_trx_lines ctl1,
5432                       ra_cust_trx_line_salesreps ctls1
5433              WHERE    ctl1.customer_trx_line_id = ctls1.customer_trx_line_id
5434              AND      ctls.customer_trx_line_id = ctls1.customer_trx_line_id
5435              GROUP BY ctls1.customer_trx_line_id,
5436                       ctl1.extended_amount,
5437                       ctls.revenue_amount_split,
5438                       ctls.revenue_percent_split
5439            )
5440    WHERE   ctls.cust_trx_line_salesrep_id in
5441            (
5442              SELECT   MIN(cust_trx_line_salesrep_id)
5443              FROM     ra_cust_trx_line_salesreps ctls,
5444                       ra_customer_trx_lines ctl
5445              WHERE    ctl.customer_trx_line_id = ctls.customer_trx_line_id
5446              AND      ctl.customer_trx_id      = p_customer_trx_id
5447              GROUP BY ctls.customer_trx_line_id,
5448                       ctl.extended_amount
5449              HAVING   (
5450                        -- Check Revenue Amount Split
5451                         ctl.extended_amount <> SUM(
5452                                              NVL(ctls.revenue_amount_split, 0)
5453                                                   )  AND
5454                         100 = SUM(
5455                                     NVL(ctls.revenue_percent_split, 0)
5456                                   )
5457                       )
5458                     OR
5459                       -- Check Revenue Percent Split
5460                       (
5461                          100   <> SUM(
5462                                        NVL(ctls.revenue_percent_split, 0)
5463                                      ) AND
5464                          ctl.extended_amount = SUM(
5465                                             NVL(ctls.revenue_amount_split, 0)
5466                                                   )
5467                       )
5468            );
5469 
5470    l_count := sql%rowcount;
5471 
5472   IF PG_DEBUG in ('Y', 'C') THEN
5473      arp_util.debug('Salescredit Revenue Errors Corrected    : ' || l_count);
5474   END IF;
5475 
5476    p_rows_processed := l_count;
5477 
5478    arp_util.print_fcn_label( 'arp_rounding.correct_scredit_rounding_errs()- ');
5479 
5480 EXCEPTION
5481    WHEN OTHERS THEN
5482 
5483     ROLLBACK TO SAVEPOINT ARPLBCRE_2;
5484 
5485     IF PG_DEBUG in ('Y', 'C') THEN
5486        arp_util.debug('EXCEPTION:  arp_rounding.correct_scredit_rounding_errs()');
5487        arp_util.debug('p_customer_trx_id = ' || p_customer_trx_id);
5488     END IF;
5489 
5490 
5491     RAISE;
5492 
5493 end correct_scredit_rounding_errs;
5494 
5495 BEGIN
5496    /* 7039838 - Detect if this is an autoinvoice session.  If so,
5497       set g_autoinv to TRUE, otherwise FALSE.  This will
5498       impact the content of several sqls in this package
5499       for performance tuning.  */
5500    BEGIN
5501       SELECT req.request_id
5502       INTO   g_autoinv_request_id
5503       FROM  fnd_concurrent_programs prog,
5504             fnd_concurrent_requests req
5505       WHERE req.request_id = FND_GLOBAL.CONC_REQUEST_ID
5506       AND   req.concurrent_program_id = prog.concurrent_program_id
5507       AND   prog.application_id = 222
5508       AND   prog.concurrent_program_name = 'RAXTRX';
5509 
5510       IF g_autoinv_request_id is not NULL
5511       THEN
5512          g_autoinv := TRUE;
5513       ELSE
5514          /* Dummy condition, never gets executed */
5515          g_autoinv := FALSE;
5516       END IF;
5517 
5518    EXCEPTION
5519       WHEN OTHERS THEN
5520          g_autoinv := FALSE;
5521    END;
5522 END ARP_ROUNDING;