DBA Data[Home] [Help]

PACKAGE BODY: APPS.AP_INVOICE_LINES_UTILITY_PKG

Source


1 PACKAGE BODY AP_INVOICE_LINES_UTILITY_PKG AS
2 /* $Header: apilnutb.pls 120.31.12010000.3 2009/02/11 12:02:20 asansari ship $ */
3 
4 /*=============================================================================
5  |  FUNCTION - get_encumbered_flag()
6  |
7  |  DESCRIPTION
8  |      returns the invoice-level encumbrance status of an invoice.
9  |      Establish the invoice line level encumbrance flag.
10  |      Function will return one of the following statuses
11  |       'Y' - Fully encumbered
12  |       'P' - One or more distributions is encumbered, but not all
13  |       'N' - No distributions are encumbered
14  |       ''  - Budgetary control disabled
15  |  PARAMETERS
16  |      p_invoice_id - invoice id
17  |      p_line_number - invoice line number
18  |
19  |  NOTES
20  |      -- Meaning of distribution encumbrance_flag:
21  |      -- Y: Regular line, has already been successfully encumbered by AP.
22  |      -- W: Regular line, has been encumbered in advisory mode even though
23  |      --    insufficient funds existed.
24  |      -- H: Line has not been encumbered yet, since it was put on hold.
25  |      -- N or Null : Line not yet seen by this code.
26  |      -- D: Same as Y for reversal distribution line.
27  |      -- X: Same as W for reversal distribution line.
28  |      -- P: Same as H for reversal distribution line.
29  |      -- R: Same as N for reversal distribution line.
30  |
31  |  MODIFICATION HISTORY
32  |  Date         Author             Description of Change
33  |
34  *============================================================================*/
35 
36     FUNCTION get_encumbered_flag(
37                  p_invoice_id  IN  NUMBER,
38                  p_line_number IN  NUMBER )
39     RETURN VARCHAR2
40     IS
41       l_purch_encumbrance_flag    VARCHAR2(1) := '';
42       l_encumbered_flag           VARCHAR2(1) := '';
43       l_distribution_count        number      := 0;
44       l_encumbered_count          number      := 0;
45       l_org_id                    FINANCIALS_SYSTEM_PARAMS_ALL.ORG_ID%TYPE;
46 
47       CURSOR encumbrance_flag_cursor is
48       SELECT nvl(encumbered_flag,'N')
49       FROM   ap_invoice_distributions
50       WHERE  invoice_id = p_invoice_id
51         AND  invoice_line_number = p_line_number;
52     BEGIN
53 
54       SELECT NVL(fsp.purch_encumbrance_flag,'N'),
55              ai.org_id
56         INTO l_purch_encumbrance_flag,
57              l_org_id
58         FROM ap_invoices_all ai,
59              financials_system_params_all fsp
60        WHERE ai.invoice_id = p_invoice_id
61          AND ai.org_id = fsp.org_id;
62 
63       IF (l_purch_encumbrance_flag = 'N') THEN
64         RETURN(NULL);
65       END IF;
66 
67       OPEN encumbrance_flag_cursor;
68       LOOP
69       FETCH encumbrance_flag_cursor INTO l_encumbered_flag;
70       EXIT WHEN encumbrance_flag_cursor%NOTFOUND;
71         IF (l_encumbered_flag in ('Y','D', 'W','X')) THEN
72           l_encumbered_count := l_encumbered_count + 1;
73         END IF;
74           l_distribution_count := l_distribution_count + 1;
75       END LOOP;
76 
77       IF (l_encumbered_count > 0) THEN
78         -- At least one distribution is encumbered
79         IF (l_distribution_count = l_encumbered_count) THEN
80           -- Invoice Line is fully encumbered
81           RETURN('Y');
82         ELSE
83           -- Invoice Line is partially encumbered
84           RETURN('P');
85         END IF;
86       ELSE
87         -- No distributions are encumbered
88         RETURN('N');
89       END IF;
90 
91      END get_encumbered_flag;
92 
93 
94 /*=============================================================================
95  |  FUNCTION -  get_posting_status
96  |
97  |  DESCRIPTION
98  |      returns the invoice line posting status.
99  |
100  |  PARAMETER
101  |      p_invoice_id - invoice id
102  |      p_line_number - invoice line number
103  |
104  |  NOTES
105  |      'Y' - Posted
106  |      'S' - Selected
107  |      'P' - Partial
108  |      'N' - Unposted
109  |      ---------------------------------------------------------------------
110  |      -- Declare cursor to establish the invoice-level posting flag
111  |      --
112  |      -- The first two selects simply look at the posting flags (cash and/or
113  |      -- accrual) for the distributions.  The rest is to cover one specific
114  |      -- case when some of the distributions are fully posting (Y) and some
115  |      -- are unposting (N).  The status should be partial (P).
116  |      --
117  |      -- MOAC.  Use ap_invoice_distributions_all table instead of SO view
118  |      -- since this procedure is called when policy context is not set to
119  |      -- the corresponding OU for the invoice_id
120  |
121  |  MODIFICATION HISTORY
122  |  Date         Author             Description of Change
123  |  28-MAY-04    yicao              SLA Obsolescence: Remove some accounting
124  |                                  related options
125  *============================================================================*/
126    FUNCTION get_posting_status(
127                  p_invoice_id   IN NUMBER,
128                  p_line_number  IN NUMBER )
129     RETURN VARCHAR2
130     IS
131 
132       invoice_line_posting_flag           VARCHAR2(1);
133       distribution_posting_flag           VARCHAR2(1);
134       l_cash_basis_flag                   VARCHAR2(1);
135       l_org_id                            AP_SYSTEM_PARAMETERS_ALL.ORG_ID%TYPE;
136 
137 
138       CURSOR posting_cursor IS
139       SELECT cash_posted_flag
140       FROM   ap_invoice_distributions_all
141       WHERE  invoice_id = p_invoice_id
142       AND    invoice_line_number = p_line_number
143       AND    l_cash_basis_flag = 'Y'
144       UNION
145       SELECT accrual_posted_flag
146       FROM   ap_invoice_distributions_all
147       WHERE  invoice_id = p_invoice_id
148       AND    invoice_line_number = p_line_number
149       AND    l_cash_basis_flag <> 'Y'
150       UNION
151       SELECT 'P'
152       FROM   ap_invoice_distributions_all
153       WHERE  invoice_id = p_invoice_id
154       AND    invoice_line_number = p_line_number
155       AND    ( (cash_posted_flag  = 'Y'
156                 AND l_cash_basis_flag = 'Y')
157               OR
158                 (accrual_posted_flag = 'Y'
159                  AND l_cash_basis_flag <> 'Y'))
160       AND EXISTS
161                (SELECT 'An N is also in the valid flags'
162                 FROM   ap_invoice_distributions_all
163                 WHERE  invoice_id = p_invoice_id
164                 AND    invoice_line_number = p_line_number
165                 AND    ((cash_posted_flag  = 'N'
166                          AND l_cash_basis_flag = 'Y')
167                 OR
168                        (accrual_posted_flag  = 'N'
169                          AND l_cash_basis_flag <> 'Y')));
170 
171     BEGIN
172 
173     /*-----------------------------------------------------------------+
174     |  Get Accounting Methods from gl_sets_of_books                    |
175     |      l_cash_basis_flag: 'Y' --cash basis                         |
176     |                         'N' --accrual basis                      |
177     |  MOAC.  Added org_id to select statement.                        |
178     +-----------------------------------------------------------------*/
179 
180       SELECT nvl(sob.sla_ledger_cash_basis_flag, 'N'),
181              asp.org_id
182       INTO l_cash_basis_flag,
183            l_org_id
184       FROM ap_invoices_all ai,
185            ap_system_parameters_all asp,
186            gl_sets_of_books sob
187       WHERE ai.invoice_id = p_invoice_id
188       AND ai.org_id = asp.org_id
189       AND asp.set_of_books_id = sob.set_of_books_id;
190 
191       invoice_line_posting_flag := 'X';
192 
193       OPEN posting_cursor;
194 
195       LOOP
196       FETCH posting_cursor INTO distribution_posting_flag;
197       EXIT WHEN posting_cursor%NOTFOUND;
198 
199         IF (distribution_posting_flag = 'S') THEN
200           invoice_line_posting_flag := 'S';
201         ELSIF (distribution_posting_flag = 'P' AND
202                invoice_line_posting_flag <> 'S') THEN
203           invoice_line_posting_flag := 'P';
204         ELSIF (distribution_posting_flag = 'N' AND
205                invoice_line_posting_flag NOT IN ('S','P')) THEN
206           invoice_line_posting_flag := 'N';
207         ELSIF (invoice_line_posting_flag NOT IN ('S','P','N')) THEN
208           invoice_line_posting_flag := 'Y';
209         END IF;
210       END LOOP;
211       CLOSE posting_cursor;
212 
213       if (invoice_line_posting_flag = 'X') then
214         invoice_line_posting_flag := 'N';
215       end if;
216 
217       RETURN(invoice_line_posting_flag);
218     END get_posting_status;
219 
220 /*============================================================================
221  |  FUNCTION - get_approval_status
222  |
223  |  DESCRIPTION
224  |      returns the invoice line level approval status lookup code.
225  |
226  |  PARAMETERS
227  |      p_invoice_id - invoice id
228  |      p_line_number - invoice line number
229  |
230  |
231  |  NOTES
232  |      Invoices Line  -'APPROVED'
233  |                      'NEEDS REAPPROVAL'
234  |                      'NEVER APPROVED'
235  |                      'CANCELLED'
236  |
237  |  MODIFICATION HISTORY
238  |  Date         Author             Description of Change
239  |
240  *============================================================================*/
241 
242     FUNCTION get_approval_status(
243                  p_invoice_id               IN NUMBER,
244                  p_line_number              IN NUMBER)
245     RETURN VARCHAR2
246     IS
247 
248       invoice_line_approval_status    VARCHAR2(25);
249       invoice_line_approval_flag      VARCHAR2(1);
250       distribution_approval_flag      VARCHAR2(1);
251       encumbrance_flag                VARCHAR2(1);
252       invoice_holds                   NUMBER;
253       sum_distributions               NUMBER;
254       dist_var_hold                   NUMBER;
255       match_flag_cnt                  NUMBER;
256       l_cancelled_count               NUMBER;
257       l_discarded_count               NUMBER;
258       l_org_id                        FINANCIALS_SYSTEM_PARAMS_ALL.ORG_ID%TYPE;
259       ---------------------------------------------------------------------
260       -- Declare cursor to establish the invoice-level approval flag
261       --
262       -- The first select simply looks at the match status flag for the
263       -- distributions.  The rest is to cover one specific case when some
264       -- of the distributions are tested (T or A) and some are untested
265       -- (NULL).  The status should be needs reapproval (N).
266       --
267       CURSOR approval_cursor IS
268       SELECT nvl(match_status_flag, 'N')
269       FROM   ap_invoice_distributions_all
270       WHERE  invoice_id = p_invoice_id
271       AND    invoice_line_number =  p_line_number;
272 
273     BEGIN
274 
275          ---------------------------------------------------------------------
276          -- Get the encumbrance flag
277          -- MOAC.  Included select from ap_invoices_all to get the org_id from
278          --        the invoice_id since it is unique
279 
280       SELECT NVL(fsp.purch_encumbrance_flag,'N'), ai.org_id
281       INTO encumbrance_flag, l_org_id
282       FROM ap_invoices_all ai,
283            financials_system_params_all fsp
284       WHERE ai.invoice_id = p_invoice_id
285       AND ai.org_id = fsp.org_id;
286 
287          ---------------------------------------------------------------------
288          -- Get the number of holds for the invoice
289          --
290       SELECT count(*)
291       INTO   invoice_holds
292       FROM   ap_holds_all
293       WHERE  invoice_id = p_invoice_id
294       AND    release_lookup_code is NULL;
295 
296          ---------------------------------------------------------------------
297          -- Check if DIST VAR hold is placed on this invoice.
298          -- DIST VAR is a special case because it could be placed
299          -- when no distributions exist and in this case, the invoice
300          -- status should be NEEDS REAPPROVAL.
301          --
302       SELECT count(*)
303       INTO   dist_var_hold
304       FROM   ap_holds_all
305       WHERE  invoice_id = p_invoice_id
306       AND    hold_lookup_code = 'DIST VARIANCE'
307       AND    release_lookup_code is NULL;
308 
309          ---------------------------------------------------------------------
310          -- If invoice is cancelled, return 'CANCELLED'.
311          --
312       SELECT count(*)
313       INTO   l_cancelled_count
314       FROM   ap_invoice_lines
315       WHERE  invoice_id = p_invoice_id
316         AND  line_number = p_line_number
317         AND  NVL(cancelled_flag, 'N' ) = 'Y';
318 
319       IF ( l_cancelled_count > 0 ) THEN
320         RETURN('CANCELLED');
321       END IF;
322 
323          ---------------------------------------------------------------------
324          -- Getting the count of distributions with
325          -- match_status_flag not null. We will open the approval_cursor
326          -- only if the count is more than 0.
327          --
328       SELECT count(*)
329       INTO match_flag_cnt
330       FROM ap_invoice_distributions_all aid
331       WHERE aid.invoice_id = p_invoice_id
332       AND aid.invoice_line_number = p_line_number
333       AND aid.match_status_flag IS NOT NULL
334       AND rownum < 2;
335 
336          ---------------------------------------------------------------------
337          -- Establish the invoice line level approval flag
338          --
339          -- Use the following ordering sequence to determine the invoice-level
340          -- approval flag:
341          --                     'N' - Needs Reapproval
342          --                     'T' - Tested
343          --                     'A' - Approved
344          --                     NULL  - Never Approved
345          --                     'X' - No Distributions Exist
346          --
347          -- Initialize invoice line level approval flag
348          --
349       invoice_line_approval_flag := 'X';
350 
351       IF match_flag_cnt > 0 THEN
352 
353         OPEN approval_cursor;
354 
355         LOOP
356         FETCH approval_cursor INTO distribution_approval_flag;
357         EXIT WHEN approval_cursor%NOTFOUND;
358 
359           IF (distribution_approval_flag IS NULL) THEN
360             invoice_line_approval_flag := NULL;
361           ELSIF (distribution_approval_flag = 'N') THEN
362             invoice_line_approval_flag := 'N';
363           ELSIF (distribution_approval_flag = 'T' AND
364                  (invoice_line_approval_flag <> 'N' or
365                   invoice_line_approval_flag is null)) THEN
366             invoice_line_approval_flag := 'T';
367           ELSIF (distribution_approval_flag = 'A' AND
368                  (invoice_line_approval_flag NOT IN ('N','T')
369                   or invoice_line_approval_flag is null)) THEN
370             invoice_line_approval_flag := 'A';
371           END IF;
372 
373         END LOOP;
374 
375         CLOSE approval_cursor;
376       END IF; -- end of match_flag_cnt
377 
378 
379          ---------------------------------------------------------------------
380          -- Derive the translated approval status from the approval flag
381          --
382       IF (encumbrance_flag = 'Y') THEN
383 
384         IF (invoice_line_approval_flag = 'A' AND invoice_holds = 0) THEN
385           invoice_line_approval_status := 'APPROVED';
386         ELSIF ((invoice_line_approval_flag in ('A') AND invoice_holds > 0)
387                OR (invoice_line_approval_flag IN ('T','N'))) THEN
388           invoice_line_approval_status := 'NEEDS REAPPROVAL';
389         ELSIF (dist_var_hold >= 1) THEN
390                  --It's assumed here that the user won't place this hold
391                  --manually before approving.  If he does, status will be
392                  --NEEDS REAPPROVAL.  dist_var_hold can result when there
393                  --are no distributions or there are but amounts don't
394                  --match.  It can also happen when an invoice is created with
395                  --no distributions, then approve the invoice, then create the
396                  --distribution.  So, in this case, although the match flag
397                  --is null, we still want to see the status as NEEDS REAPPR.
398           invoice_line_approval_status := 'NEEDS REAPPROVAL';
399         ELSIF (invoice_line_approval_flag is null
400                 OR (invoice_line_approval_flag = 'X' AND dist_var_hold = 0)) THEN
401 
402           invoice_line_approval_status := 'NEVER APPROVED';
403         END IF;
404 
405       ELSIF (encumbrance_flag = 'N') THEN
406         IF (invoice_line_approval_flag IN ('A','T') AND invoice_holds = 0) THEN
407           invoice_line_approval_status := 'APPROVED';
408         ELSIF ((invoice_line_approval_flag IN ('A','T') AND invoice_holds > 0)
409                 OR
410                (invoice_line_approval_flag = 'N')) THEN
411           invoice_line_approval_status := 'NEEDS REAPPROVAL';
412         ELSIF (dist_var_hold >= 1) THEN
413           invoice_line_approval_status := 'NEEDS REAPPROVAL';
414         ELSIF (invoice_line_approval_flag is null
415                OR (invoice_line_approval_flag = 'X' AND dist_var_hold = 0)) THEN
416                  -- A NULL flag indicate that APPROVAL has not
417                  -- been run for this invoice, therefore, even if manual
418                  -- holds exist, status should be NEVER APPROVED.
419           invoice_line_approval_status := 'NEVER APPROVED';
420         END IF;
421       END IF;
422 
423       RETURN(invoice_line_approval_status);
424     END get_approval_status;
425 
426 /*=============================================================================
427  |  Public PROCEDURE Is_Line_Discardable
428  |
429  |      Check if the line is discardable
430  |
431  |  PROGRAM FLOW
432  |
433  |      1. return FALSE - if discard flag is Y
434  |      2. return FALSE - if line contains distribution that does not have
435  |                        an OPEN reversal period name.
436  |      3. return FALSE - if line contain distributions which are PO/RCV
437  |                        matched whose reversal causes amount/qty billed less
438  |                        than 0
439  |      4. return FALSE - if line is final match
440  |      5. return FALSE - if line is referenced by an active correction
441  |      6. return FALSE - if line contains distributions witn invalid account
442  |      7. return FALSE - if line contains distributions refereced by active
443  |                        distributions which are not cancelled or reversed
444  |                        apply to FREIGHT/MISC allocated to Item Line
445  |      8. return FALSE - if line with outstanding allocation rule
446  |      9. return FALSE - if line is AWT line linked to AWT invoice
447  |     10. return FALSE - if prepayment line has been applied (same as Note 1)
448  |
449  |  NOTES
450  |
451  |     1. If line is the prepay application/unapplication - we handle the
452  |        business rule on-line. Means from UI we will make sure that one
453  |        PREPAY type line can not be discarded unless it is being fully
454  |        unapplied.
455  |
456  |  MODIFICATION HISTORY
457  |  Date         Author               Description of Change
458  |  03/07/03     sfeng                Created
459  |
460  *============================================================================*/
461 
462   Function Is_Line_Discardable(
463                P_line_rec          IN  ap_invoice_lines%ROWTYPE,
464                P_error_code            OUT NOCOPY VARCHAR2,
465                P_calling_sequence  IN             VARCHAR2) RETURN BOOLEAN
466 
467   IS
468 
469     l_po_dist_count              NUMBER := 0;
470     l_rcv_dist_count             NUMBER := 0; --Bug5000472
471     l_reference_count            NUMBER := 0;
472     l_active_count               NUMBER := 0;
473     l_quick_credit_count         NUMBER := 0;
474     l_quick_credit_ref_count     NUMBER := 0;
475     l_invalid_acct_count         NUMBER := 0;
476     l_final_close_count          NUMBER := 0;
477     l_pending_count              NUMBER := 0;
478     l_count                      NUMBER := 0;
479 
480     l_debug_info                 VARCHAR2(240);
481     l_curr_calling_sequence      VARCHAR2(2000);
482 
483     TYPE date_tab is TABLE OF DATE INDEX BY BINARY_INTEGER;
484     l_gl_date_list               date_tab;
485     i                            BINARY_INTEGER := 1;
486     l_open_gl_date               DATE :='';
487     l_open_period                gl_period_statuses.period_name%TYPE := '';
488 
489     l_prepay_amount_applied      NUMBER := 0;
490     l_enc_enabled                VARCHAR2(1);    --bug6009101
491     l_po_not_approved            VARCHAR2(1);    --bug6009101
492     l_org_id  ap_invoices_all.org_id%type;      -- for bug 5936290
493     CURSOR dist_gl_date_Cur IS
494     SELECT accounting_date
495       FROM ap_invoice_distributions AID
496      WHERE AID.invoice_id = p_line_rec.invoice_id
497        AND AID.invoice_line_number = p_line_rec.line_number
498        AND NVL(AID.reversal_flag, 'N') <> 'Y';
499 
500 
501   BEGIN
502 
503     l_curr_calling_sequence := 'AP_INVOICE_LINE_PKG.IS_Line_Discardable<-' ||
504                                P_calling_sequence;
505 
506     /*-----------------------------------------------------------------+
507      |  Step 0 - If line is discarded, return FALSE                    |
508      +-----------------------------------------------------------------*/
509 
510     l_debug_info := 'Check if line is already discarded';
511 
512     IF ( NVL(p_line_rec.discarded_flag, 'N') = 'Y' ) THEN
513       p_error_code := 'AP_INV_LINE_ALREADY_DISCARDED';
514       RETURN FALSE;
515     END IF;
516 
517     /*-----------------------------------------------------------------+
518      |  Step 1 - If line is CANCELLED, can not be discarded, return    |
519      |           FALSE                                                 |
520      +-----------------------------------------------------------------*/
521 
522     l_debug_info := 'Check if line is already cancelled';
523 
524     IF ( NVL(p_line_rec.cancelled_flag, 'N') = 'Y' ) THEN
525       p_error_code := 'AP_INV_CANCELLED';
526       RETURN FALSE;
527     END IF;
528 
529     /*-----------------------------------------------------------------+
530      |  Step 2 - If line contains distribution which has no open       |
531      |           period, can not be discarded, return FALSE            |
532      +-----------------------------------------------------------------*/
533 
534     l_debug_info := 'Check if distribution in this line has open period';
535 
536     OPEN dist_gl_date_Cur;
537     FETCH dist_gl_date_Cur
538     BULK COLLECT INTO l_gl_date_list;
539     CLOSE dist_gl_date_Cur;
540 
541   -- For bug 5936290
542   --  we call ap_utilities_pkg.get_current_gl_date
543   --  and in ap_utilities_pkg.get_open_gl_date for getting the gl date and
544   --  period below.For both these procedures one parameter is org_id
545   --  and it's default value is mo_global.get_current_org_id.we do
546   --  were not passing the org_id in these procedures calls so
547   --  the org_id was getting picked up from mo_global.get_current_org_id
548   --  and it's coming null when the Invoice batch option is ON.
549   --  So now we are passing the org_id also in these two calls.
550 
551     SELECT org_id
552     INTO   l_org_id
553     FROM   ap_invoices_all
554     WHERE  invoice_id = p_line_rec.invoice_id;
555 
556     FOR i in NVL(l_gl_date_list.FIRST,0)..NVL(l_gl_date_list.LAST,-1)
557     LOOP
558       l_open_period := ap_utilities_pkg.get_current_gl_date(l_gl_date_list(i),l_org_id); --added for bug 5936290
559 
560       IF ( l_open_period IS NULL ) THEN
561         ap_utilities_pkg.get_open_gl_date(
562                  l_gl_date_list(i),
563                  l_open_period,
564                  l_open_gl_date,
565                  l_org_id); --added for bug 5936290
566         IF ( l_open_period IS NULL ) THEN
567           p_error_code := 'AP_DISCARD_NO_FUTURE_PERIODS';
568           RETURN FALSE;
569         END IF;
570       END IF;
571     END LOOP;
572 
573     /*-----------------------------------------------------------------+
574      |  Step 3. if the quantity billed and amount on PO would be       |
575      |          reduced to less than zero then return FALSE            |
576      |          Always allow Reversal distributions to be cancelled    |
577      +-----------------------------------------------------------------*/
578 
579     l_debug_info := 'Check if quantity_billed on po_distribution is '
580                     || 'would be reduced to < 0';
581     --Bug5000472 added condition on po distribution id and rcv_transaction_id
582     --and commented GROUP BY in sub queries
583 
584     -- Modified the below select statment for the bug #6913924 to consider the
585     -- case when prepayment invoice matched to a PO and receipt and with
586      --different UOM for PO and receipt.
587 
588     BEGIN
589     SELECT count(*)
590     INTO   l_po_dist_count
591     FROM   po_distributions_all POD,
592            ap_invoice_distributions AID,
593            ap_invoices ai,
594            po_line_locations PLL,
595            po_lines PL
596     WHERE  POD.po_distribution_id = AID.po_distribution_id
597     AND    POD.line_location_id = PLL.line_location_id
598     AND    PLL.po_line_id = PL.po_line_id
599     AND    AID.invoice_id = ai.invoice_id
600     AND    AID.invoice_id = p_line_rec.invoice_id
601     AND    POD.org_id = AID.org_id
602     AND    AID.invoice_line_number = p_line_rec.line_number
603     AND    NVL(AID.reversal_flag,'N')<>'Y'
604     AND    aid.rcv_transaction_id is null  --Bug5000472
605     HAVING (
606             (DECODE(ai.invoice_type_lookup_code,'PREPAYMENT',
607                SUM(NVL(POD.quantity_financed, 0)),
608 	           SUM(NVL(POD.quantity_billed, 0)))
609                 -
610                 SUM(round(decode(AID.dist_match_type,
611                                 'PRICE_CORRECTION', 0,
612                                 'AMOUNT_CORRECTION', 0,
613                                  'ITEM_TO_SERVICE_PO', 0,
614                                  'ITEM_TO_SERVICE_RECEIPT', 0,
615                                   nvl( AID.quantity_invoiced, 0 ) +
616                                   nvl( AID.corrected_quantity,0 )
617                ) *
618                      po_uom_s.po_uom_convert(AID.matched_uom_lookup_code,
619                                    nvl(PLL.unit_meas_lookup_code,
620                      PL.unit_meas_lookup_code),
621                  PL.item_id), 15))
622               < 0)
623                OR (DECODE(ai.invoice_type_lookup_code,'PREPAYMENT',
624                   SUM(NVL(POD.amount_financed, 0)),
625 		     SUM(NVL(POD.amount_billed, 0))) -
626                   SUM(NVL(AID.amount, 0)) < 0 ))
627        GROUP BY ai.invoice_type_lookup_code,AID.po_distribution_id;
628 
629      EXCEPTION
630        WHEN NO_DATA_FOUND THEN
631          l_po_dist_count := 0;
632     END;
633       -- end of changes for bug #6913924
634 
635     IF (l_po_dist_count > 0  ) THEN
636       P_error_code := 'AP_INV_LINE_QTY_BILLED_NOT_NEG';
637       RETURN FALSE;
638     END IF;
639 
640 --Bug5000472  Added the following block of code
641     /*-----------------------------------------------------------------+
642      |  Step 3.1. if the quantity billed and amount on RCV would be    |
643      |          reduced to less than zero then return FALSE            |
644      |          Always allow Reversal distributions to be cancelled    |
645      +-----------------------------------------------------------------*/
646 
647     l_debug_info := 'Check if quantity_billed on rcv_transactions '
648                     || 'would be reduced to < 0';
649 
650     SELECT count(*)
651     INTO   l_rcv_dist_count
652     FROM   rcv_transactions RT,
653            ap_invoice_distributions_all AID
654     WHERE  RT.transaction_id = AID.rcv_transaction_id
655     AND    AID.invoice_id = p_line_rec.invoice_id
656     AND    AID.invoice_line_number = p_line_rec.line_number
657     AND    AID.rcv_transaction_id is not null
658     AND    NVL(AID.reversal_flag,'N')<>'Y'
659     AND    (NVL(rt.quantity_billed,0) <
660                (SELECT SUM(decode( AID1.dist_match_type,
661                                   'PRICE_CORRECTION', 0,
662                                   'AMOUNT_CORRECTION', 0,
663                                   'ITEM_TO_SERVICE_PO', 0,
664                                   'ITEM_TO_SERVICE_RECEIPT', 0,
665                                    nvl( AID1.corrected_quantity,0 ) +
666                                    nvl( AID1.quantity_invoiced,0 )
667                                                         )
668                                                     )
669                  FROM ap_invoice_distributions_all aid1
670                 WHERE aid1.invoice_id = aid.invoice_id
671                   AND aid1.invoice_line_number = aid.invoice_line_number
672                   AND aid1.rcv_transaction_id=aid.rcv_transaction_id
673                        )
674              OR
675              NVL(rt.amount_billed,0) <  (
676                        SELECT SUM(NVL(AID2.amount,0))
677                          FROM ap_invoice_distributions_all aid2
678                         WHERE aid2.invoice_id = aid.invoice_id
679                          AND aid2.invoice_line_number = aid.invoice_line_number
680                          AND aid2.rcv_transaction_id=aid.rcv_transaction_id
681                           )
682              );
683 
684     IF (l_rcv_dist_count > 0  ) THEN
685       P_error_code := 'AP_INV_LINE_QTY_BILLED_NOT_NEG';
686       RETURN FALSE;
687     END IF;
688 --Bug5000472 End
689 
690     /*-----------------------------------------------------------------+
691      |  Step 4. If invoice is matched to a Finally Closed PO, return   |
692      |          FALSE                                                  |
693      +-----------------------------------------------------------------*/
694 
695     l_debug_info := 'Check if invoice line is matched to a finally'
696                     ||'  closed PO shipment';
697 
698     SELECT count(*)
699     INTO   l_final_close_count
700     FROM   ap_invoice_lines AIL,
701            po_line_locations PLL
702     WHERE  AIL.invoice_id = p_line_rec.invoice_id
703     AND    AIL.line_number = p_line_rec.line_number
704     AND    AIL.po_line_location_id = PLL.line_location_id
705     AND    PLL.closed_code = 'FINALLY CLOSED';
706 
707     IF (l_final_close_count > 0) THEN
708       P_error_code := 'AP_INV_LINE_PO_FINALLY_CLOSED';
709       RETURN FALSE;
710     END IF;
711 
712     /*-----------------------------------------------------------------+
713      |  Step 4.1 If the encumbrance is on and the invoice is matched to
714      |           to an unapproved PO, then do not allow discard.(bug6009101)
715      +-----------------------------------------------------------------*/
716 
717       SELECT NVL(purch_encumbrance_flag,'N')
718       INTO   l_enc_enabled
719       FROM   financials_system_params_all FSP,
720              ap_invoices_all              AI
721       WHERE  AI.invoice_id  =  p_line_rec.invoice_id
722       AND    FSP.org_id     =  AI.org_id;
723 
724     if l_enc_enabled  = 'Y' then
725 
726        begin
727 
728           select 'Y'
729           into   l_po_not_approved
730           from   po_headers POH
731           where POH.po_header_id = p_line_rec.po_header_id
732           and   POH.approved_flag <> 'Y';    --bug6653070
733 
734           EXCEPTION
735              WHEN OTHERS THEN
736                   NULL;
737 
738        end;
739 
740        if l_po_not_approved = 'Y' then
741           p_error_code := 'AP_PO_UNRES_CANT_DISC_LINE';
742           return FALSE;
743        end if;
744    end if;
745 
746 
747     /*-----------------------------------------------------------------+
748      |  Step 5. If invoice is a quick credit, it can be cancelled at   |
749      |          at header level. can not discard individual line. so   |
750      |          return FALSE;                                          |
751      +-----------------------------------------------------------------*/
752     l_debug_info := 'Check if this invoice is a quick credit';
753 
754     SELECT count(*)
755       INTO l_quick_credit_count
756       FROM ap_invoices AI
757      WHERE AI.invoice_id = p_line_rec.invoice_id
758        AND NVL(AI.quick_credit, 'N') = 'Y';
759 
760     IF ( l_quick_credit_count > 0  ) THEN
761       P_error_code := 'AP_INV_IS_QUICK_CREDIT';
762       RETURN FALSE;
763     END IF;
764 
765     /*-----------------------------------------------------------------+
766      |  Step 6. Check If invoice line is actively referenced           |
767      |         If invoice line reference by an active                  |
768      |                  correction, return FALSE                       |
769      +-----------------------------------------------------------------*/
770     l_debug_info := 'Check if this line is refrenced by a correction';
771 
772     SELECT count(*)
773       INTO l_active_count
774       FROM ap_invoice_lines AIL
775      WHERE NVL( AIL.discarded_flag, 'N' ) <> 'Y'
776        AND NVL( AIL.cancelled_flag, 'N' ) <> 'Y'
777        AND AIL.corrected_inv_id = p_line_rec.invoice_id
778        AND AIL.corrected_line_number = p_line_rec.line_number;
779 
780     IF ( l_active_count > 0) THEN
781       P_error_code := 'AP_INV_LINE_REF_BY_CORRECTION';
782       RETURN FALSE;
783     END IF;
784 
785     /*-----------------------------------------------------------------+
786      |  Step 7. Check If invoice line is actively referenced           |
787      |          If one active quick credit is referencing this         |
788      |          invoice, return FALSE                                  |
789      +-----------------------------------------------------------------*/
790     l_debug_info := 'Check if this line is a refreced by a quick credit';
791 
792     -- Bug 5261908. Added rownum condition to improve performance
793     BEGIN
794     --bug 5475668 Added the if condition.
795     --bug 8208823 Added condition for line_type_lookup_code
796     if (p_line_rec.invoice_id is not NULL
797 	AND p_line_rec.line_type_lookup_code <> 'PREPAY') then
798       SELECT 1
799         INTO l_quick_credit_ref_count
800         FROM ap_invoices AI
801        WHERE AI.credited_invoice_id = p_line_rec.invoice_id
802          AND NVL(AI.quick_credit, 'N') = 'Y'
803          AND AI.cancelled_date is null
804          AND Rownum = 1;
805     end if;
806     EXCEPTION
807       WHEN no_data_found THEN
808            NULL;
809     END;
810 
811     IF (l_quick_credit_ref_count > 0  ) THEN
812       P_error_code := 'AP_INV_LINE_REF_BY_QCK_CREDIT';
813       RETURN FALSE;
814     END IF;
815 
816 
817     /*-----------------------------------------------------------------+
818      |  Step 8. If line contain distributions which has invalid account |
819      |          return FALSE                                            |
820      +-----------------------------------------------------------------*/
821 
822     SELECT  count(*)
823     INTO    l_invalid_acct_count
824     FROM    ap_invoice_distributions D
825     WHERE   D.invoice_id = p_line_rec.invoice_id
826     AND     D.invoice_line_number = p_line_rec.line_number
827     AND     D.posted_flag IN ('N', 'P')
828     AND ((EXISTS (select 'x'
829                   from gl_code_combinations C
830                   where D.dist_code_combination_id = C.code_combination_id (+)
831                   and (C.code_combination_id is null
832                      or C.detail_posting_allowed_flag = 'N'
833                      or C.start_date_active > D.accounting_date
834                      or C.end_date_active < D.accounting_date
835                      or C.template_id is not null
836                      or C.enabled_flag <> 'Y'
837                      or C.summary_flag <> 'N'
838                      )))
839     OR (D.dist_code_combination_id = -1));
840 
841     IF (l_invalid_acct_count <> 0) THEN
842 
843       P_error_code := 'AP_INV_LINE_INVALID_DIST_ACCT';
844       RETURN FALSE;
845     END IF;
846 
847     /*-----------------------------------------------------------------+
848      |  Step 9. If line contain distributions referenced by active     |
849      |          distributions, return FALSE. This applies to all the   |
850      |          non-charge lines which have active charges lines       |
851      |          allocated to themselves. In case that a charge         |
852      |          distribution's parent line is not a charge line but    |
853      |          and ITEM/ACCRUAL line, we should allow line to be      |
854      |          discarded                                              |
855      +-----------------------------------------------------------------*/
856 -- Bug 5114543
857 -- Commented the following check to allow discard of item line
858 -- when it has allocated charges.
859 -- Bug 5386077. Recommenting again. Was checked incorrectly via bug 5000472 (120.20)
860 
861 /*
862     SELECT  count(*)
863     INTO    l_reference_count
864     FROM    ap_invoice_distributions AID
865     WHERE   NVL(AID.cancellation_flag, 'N') <> 'Y'
866     AND     NVL(AID.reversal_flag, 'N') <> 'Y'
867     AND     AID.invoice_id = p_line_rec.invoice_id
868     AND     AID.invoice_line_number <> p_line_rec.line_number
869     AND     AID.charge_applicable_to_dist_id IS NOT NULL
870     AND     AID.charge_applicable_to_dist_id IN
871             ( SELECT AID2.invoice_distribution_id
872                 FROM ap_invoice_distributions AID2
873                WHERE AID2.invoice_id = p_line_rec.invoice_id
874                  AND AID2.invoice_line_number = p_line_rec.line_number
875                  AND NVL(AID2.cancellation_flag, 'N') <> 'Y'
876                  AND NVL(AID2.reversal_flag, 'N') <> 'Y' );
877 
878     IF ( l_reference_count <> 0) THEN
879       P_error_code := 'AP_INV_LINE_ACTIVE_DIST';
880       RETURN FALSE;
881     END IF;
882 */
883     /*------------------------------------------------------------------+
884      |  Step 10. If this non-charge line contain active allocation rule |
885      |           which is not yet applied, return FALSE                 |
886      +------------------------------------------------------------------*/
887 -- Bug 5114543
888 -- Commented the following check to allow discard of item line
889 -- when it has allocated charges.
890 -- Bug 5386077. Recommenting again. Was checked incorrectly via bug 5000472 (120.20).
891 /*
892     SELECT  count(*)
893     INTO    l_pending_count
894     FROM    ap_allocation_rules  AR,
895             ap_allocation_rule_lines ARL
896     WHERE   AR.invoice_id = p_line_rec.invoice_id
897     AND     AR.invoice_id = ARL.invoice_id
898     AND     AR.chrg_invoice_line_number = ARL.chrg_invoice_line_number
899     AND     ARL.to_invoice_line_number = p_line_rec.line_number
900     AND     AR.status = 'PENDING';
901 
902     IF ( l_pending_count <> 0) THEN
903       P_error_code := 'AP_INV_LINE_HAS_ALLOC_RULE';
904       RETURN FALSE;
905     END IF;
906  */
907     /*-----------------------------------------------------------------+
908      |  Step 11. If line is Automatic AWT line which invoice is fully  |
909      |          or partially paid, return FALSE                        |
910      +-----------------------------------------------------------------*/
911 
912     SELECT  count(*)
913     INTO    l_count
914     FROM    ap_invoice_lines AIL,
915             ap_invoices AI
916     WHERE   AIL.invoice_id = P_line_rec.invoice_id
917     AND     AIL.line_number = P_line_rec.line_number
918     AND     AIL.line_type_lookup_code  = 'AWT'
919     AND     NOT EXISTS ( SELECT invoice_distribution_id
920                            FROM ap_invoice_distributions aid
921                           WHERE aid.invoice_id = AIL.invoice_id
922                             AND aid.invoice_line_number = AIL.line_number
923                             AND awt_flag = 'M' )
924     AND     AI.invoice_id = AIL.invoice_id
925     AND     AI.payment_status_flag in ('P', 'Y');
926 
927     IF ( l_count <> 0) THEN
928       P_error_code := 'AP_INV_LINE_IS_AWT';
929       RETURN FALSE;
930     END IF;
931 
932     /*--------------------------------------------------------------------+
933      |  Step 12. If line has some or entire retained amount
934      |           released, return FALSE
935      +--------------------------------------------------------------------*/
936 
937      SELECT count(*)
938        INTO l_count
939        FROM ap_invoice_lines AIL
940       WHERE AIL.invoice_id  = P_line_rec.invoice_id
941 	AND AIL.line_number = P_line_rec.line_number
942 	AND (ail.retained_amount           IS NOT NULL AND
943 	     ail.retained_amount_remaining IS NOT NULL AND
944              abs(ail.retained_amount) <> abs(ail.retained_amount_remaining));
945 
946      IF ( l_count <> 0) THEN
947          P_error_code := 'AP_INV_LINE_RELEASED';
948          RETURN FALSE;
949      END IF;
950 
951     /*-----------------------------------------------------------------+
952      |  Step 13. Prepayment line cannot be discarded after prepayment  |
953      |           is applied.  If so, return FALSE (Bug #5114854)       |
954      +-----------------------------------------------------------------*/
955     SELECT count(*)
956       INTO l_count
957       FROM ap_invoices_all ai
958      WHERE invoice_id = p_line_rec.invoice_id
959        AND invoice_type_lookup_code = 'PREPAYMENT';
960 
961     IF ( l_count > 0 ) THEN
962 
963       l_prepay_amount_applied :=
964          ap_invoices_pkg.get_prepay_amount_applied(p_line_rec.invoice_id);
965 
966       if (l_prepay_amount_applied <> 0) then
967          p_error_code := 'AP_INV_DEL_APPLIED_PREPAY';
968          RETURN FALSE;
969       end if;
970     END IF;
971 
972     P_error_code := null;
973     RETURN TRUE;
974 
975   EXCEPTION
976     WHEN OTHERS THEN
977       IF (SQLCODE <> -20001) THEN
978         FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
979         FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
980         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',l_curr_calling_sequence);
981         FND_MESSAGE.SET_TOKEN('PARAMETERS',
982              ' P_invoice_id = '     || p_line_rec.invoice_id
983           ||' P_line_number = '     || p_line_rec.line_number );
984         FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
985       END IF;
986 
987       IF ( dist_gl_date_Cur%ISOPEN ) THEN
988         CLOSE dist_gl_date_Cur;
989       END IF;
990 
991       APP_EXCEPTION.RAISE_EXCEPTION;
992 
993   END Is_Line_Discardable;
994 
995  /*=============================================================================
996  |  Public FUNCTION Allocation_Exists
997  |
998  |      Check if the line has allocation rules and lines associated with it.
999  |
1000  |  PROGRAM FLOW
1001  |
1002  |       return TRUE  - if allocation rules and lines exist
1003  |       return FALSE - otherwise.
1004  |
1005  |  MODIFICATION HISTORY
1006  |  Date         Author               Description of Change
1007  |  03/10/13     bghose               Created
1008  *============================================================================*/
1009 
1010   FUNCTION Allocation_Exists (p_Invoice_Id        Number,
1011                               p_Line_Number       Number,
1012                               p_Calling_Sequence  Varchar2) Return Boolean Is
1013     dummy number := 0;
1014     current_calling_sequence   Varchar2(2000);
1015     debug_info                 Varchar2(100);
1016 
1017   Begin
1018     -- Update the calling sequence
1019     --
1020     current_calling_sequence :=
1021         'AP_INVOICE_LINES_UTILITY_PKG.ALLOCATION_EXISTS<-'||p_Calling_Sequence;
1022 
1023     debug_info := 'Select from ap_allocation_rules';
1024 
1025     Select count(*)
1026     Into   dummy
1027     From   ap_allocation_rules  AR,
1028            ap_allocation_rule_lines ARL
1029     Where  AR.invoice_id = p_Invoice_Id
1030     And    AR.invoice_id = ARL.invoice_id
1031     And    AR.chrg_invoice_line_number = ARL.chrg_invoice_line_number
1032     And    ARL.to_invoice_line_number = p_line_number;
1033 
1034     If (dummy >= 1) Then
1035       return  TRUE;
1036     End If;
1037 
1038     return FALSE;
1039 
1040   Exception
1041     WHEN OTHERS THEN
1042       If (SQLCODE <> -20001) Then
1043         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1044         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1045         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1046         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1047                                      ||', line number = '|| p_Line_Number);
1048         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1049       End If;
1050       APP_EXCEPTION.RAISE_EXCEPTION;
1051   End Allocation_Exists;
1052 
1053  /*=============================================================================
1054  |  Public FUNCTION Inv_Reversed_Via_Qc
1055  |
1056  |      Check if the invoice has been reversed via Qucik Credit.
1057  |
1058  |  PROGRAM FLOW
1059  |
1060  |       return TRUE  - if reversed via Quick Credit
1061  |       return FALSE - otherwise.
1062  |
1063  |  MODIFICATION HISTORY
1064  |  Date         Author               Description of Change
1065  |  03/10/13     bghose               Created
1066  *=============================================================================*/
1067 
1068   Function Inv_Reversed_Via_Qc (p_Invoice_Id        Number,
1069                                 p_Calling_Sequence  Varchar2)  Return Boolean Is
1070     dummy number := 0;
1071     current_calling_sequence   Varchar2(2000);
1072     debug_info                 Varchar2(100);
1073 
1074     Begin
1075     -- Update the calling sequence
1076     --
1077      current_calling_sequence :=
1078        'AP_INVOICE_LINES_UTILITY_PKG.Inv_Reverse_Via_Qc<-'||p_Calling_Sequence;
1079 
1080      debug_info := 'Select from ap_invoics_all';
1081 
1082      -- Bug 5261908. Added rownum condition to improve performance
1083      BEGIN
1084      --bug 5475668 Added the if condition
1085       if (p_invoice_id is not null) then
1086        Select 1
1087        Into   dummy
1088        From   ap_invoices_all AI
1089        Where AI.credited_invoice_id = p_Invoice_Id
1090        AND NVL(AI.quick_credit, 'N') = 'Y'
1091        AND AI.cancelled_date is null
1092        AND Rownum = 1;
1093       end if;
1094      EXCEPTION
1095        WHEN no_data_found THEN
1096             dummy := 0;
1097      END;
1098 
1099      If (dummy >= 1) Then
1100        return  TRUE;
1101      End if;
1102 
1103      return FALSE;
1104 
1105    Exception
1106     WHEN OTHERS THEN
1107       If (SQLCODE <> -20001) Then
1108         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1109         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1110         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1111         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id);
1112         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1113       End If;
1114       APP_EXCEPTION.RAISE_EXCEPTION;
1115   End Inv_Reversed_Via_Qc;
1116 
1117  /*=============================================================================
1118  |  Public FUNCTION Is_Line_Dists_Trans_FA
1119  |
1120  |      Check if the line has associated distributions which has transfered to
1121  |      FA.
1122  |
1123  |  PROGRAM FLOW
1124  |
1125  |       return TRUE  - ifdistributions transferred to FA
1126  |       return FALSE - otherwise.
1127  |
1128  |  MODIFICATION HISTORY
1129  |  Date         Author               Description of Change
1130  |  03/10/13     bghose               Created
1131  *============================================================================*/
1132   FUNCTION Is_Line_Dists_Trans_FA (p_Invoice_Id        Number,
1133                               p_Line_Number       Number,
1134                               p_Calling_Sequence  Varchar2) Return Boolean Is
1135     dummy number := 0;
1136     current_calling_sequence   Varchar2(2000);
1137     debug_info                 Varchar2(100);
1138 
1139   Begin
1140     -- Update the calling sequence
1141     --
1142     current_calling_sequence :=
1143         'AP_INVOICE_LINES_UTILITY_PKG.IS_LINE_DISTS_TRANS_FA<-'
1144                       ||p_Calling_Sequence;
1145 
1146     debug_info := 'Select from ap_invoice_distributions_all';
1147 
1148     Select count(*)
1149     Into   dummy
1150     From   ap_invoice_distributions_all
1151     Where invoice_id = p_Invoice_Id
1152     And invoice_line_number = p_Line_Number
1153     And assets_addition_flag = 'Y';
1154 
1155     If (dummy >= 1) Then
1156       return  TRUE;
1157     End if;
1158 
1159     return FALSE;
1160 
1161   Exception
1162     WHEN OTHERS THEN
1163       If (SQLCODE <> -20001) Then
1164         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1165         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1166         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1167         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1168                               ||', line number = '|| p_Line_Number);
1169         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1170       End If;
1171       APP_EXCEPTION.RAISE_EXCEPTION;
1172   End Is_Line_Dists_Trans_FA;
1173 
1174  /*=============================================================================
1175  |  Public FUNCTION Line_Dists_Acct_Event_Created
1176  |
1177  |      Check if the line has associated distributions accounting event created
1178  |
1179  |  PROGRAM FLOW
1180  |
1181  |       return TRUE  - if distributions accounting event created
1182  |       return FALSE - otherwise.
1183  |
1184  |  MODIFICATION HISTORY
1185  |  Date         Author               Description of Change
1186  |  03/10/13     bghose               Created
1187  *============================================================================*/
1188 
1189   FUNCTION Line_Dists_Acct_Event_Created (p_Invoice_Id        Number,
1190                                p_Line_Number       Number,
1191                                p_Calling_Sequence  Varchar2) Return Boolean Is
1192     dummy number := 0;
1193     current_calling_sequence   Varchar2(2000);
1194     debug_info                 Varchar2(100);
1195 
1196   Begin
1197     -- Update the calling sequence
1198     --
1199     current_calling_sequence :=
1200         'AP_INVOICE_LINES_UTILITY_PKG.LINE_DISTS_ACCT_EVENT_CREATED<-'
1201                       ||p_Calling_Sequence;
1202 
1203     debug_info := 'Select from ap_invoice_distributions_all';
1204 
1205     Select count(*)
1206     Into   dummy
1207     From   ap_invoice_distributions_all
1208     Where invoice_id = p_Invoice_Id
1209     And invoice_line_number = p_Line_Number
1210     And accounting_event_id Is Not Null;
1211 
1212     If (dummy >= 1) Then
1213       return  TRUE;
1214     End if;
1215 
1216     return FALSE;
1217 
1218   Exception
1219     WHEN OTHERS THEN
1220       If (SQLCODE <> -20001) Then
1221         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1222         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1223         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1224         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1225                               ||', line number = '|| p_Line_Number);
1226         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1227       End If;
1228       APP_EXCEPTION.RAISE_EXCEPTION;
1229   End Line_Dists_Acct_Event_Created;
1230 
1231  /*=============================================================================
1232  |  Public FUNCTION Line_Referred_By_Corr
1233  |
1234  |      Check if the line has been referred by any correction
1235  |
1236  |  PROGRAM FLOW
1237  |
1238  |       return TRUE  - if line has been referred by any correction
1239  |       return FALSE - otherwise.
1240  |
1241  |  MODIFICATION HISTORY
1242  |  Date         Author               Description of Change
1243  |  03/10/13     bghose               Created
1244  *============================================================================*/
1245 
1246   FUNCTION Line_Referred_By_Corr (p_Invoice_Id        Number,
1247                             p_Line_Number       Number,
1248                             p_Calling_Sequence  Varchar2) Return Boolean Is
1249     dummy number := 0;
1250     current_calling_sequence   Varchar2(2000);
1251     debug_info                 Varchar2(100);
1252 
1253   Begin
1254     -- Update the calling sequence
1255     --
1256     current_calling_sequence :=
1257         'AP_INVOICE_LINES_UTILITY_PKG.LINE_REFERRED_BY_CORR<-'
1258                       ||p_Calling_Sequence;
1259 
1260     debug_info := 'Select from ap_invoice_lines_all';
1261 
1262     Select count(*)
1263     Into   dummy
1264     From   ap_invoice_lines_all AIL
1265     Where  NVL(AIL.discarded_flag, 'N' ) <> 'Y'
1266     And NVL( AIL.cancelled_flag, 'N' ) <> 'Y'
1267     And AIL.corrected_inv_id = p_Invoice_Id
1268     And AIL.corrected_line_number = p_Line_Number;
1269 
1270     If (dummy >= 1) Then
1271       return  TRUE;
1272     End if;
1273 
1274     return FALSE;
1275 
1276   Exception
1277     WHEN OTHERS THEN
1278       If (SQLCODE <> -20001) Then
1279         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1280         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1281         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1282         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1283                               ||', line number = '|| p_Line_Number);
1284         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1285       End If;
1286       APP_EXCEPTION.RAISE_EXCEPTION;
1287   End Line_Referred_By_Corr;
1288 
1289  /*=============================================================================
1290  |  Public FUNCTION Line_Dists_Referred_By_Other
1291  |
1292  |      Check if the particular invoice line contains distributions referenced
1293  |      by active distributions
1294  |
1295  |  PROGRAM FLOW
1296  |
1297  |       return TRUE  - if line has been referenced by active distributions
1298  |       return FALSE - otherwise.
1299  |
1300  |  MODIFICATION HISTORY
1301  |  Date         Author               Description of Change
1302  |  03/10/13     bghose               Created
1303  *============================================================================*/
1304 
1305   FUNCTION Line_Dists_Referred_By_Other(p_Invoice_Id        Number,
1306                             p_Line_Number       Number,
1307                             p_Calling_Sequence  Varchar2) Return Boolean Is
1308     dummy number := 0;
1309     current_calling_sequence   Varchar2(2000);
1310     debug_info                           Varchar2(100);
1311 
1312   Begin
1313     -- Update the calling sequence
1314     --
1315     current_calling_sequence :=
1316                'AP_INVOICE_LINES_UTILITY_PKG.Line_Dists_Referred_By_Other <-'||
1317                             p_Calling_Sequence;
1318     debug_info := 'Select from ap_invoic_distributions_all';
1319 
1320     Select count(*)
1321     Into   dummy
1322     From   ap_invoice_distributions_all AID
1323     Where   NVL(AID.cancellation_flag, 'N') <> 'Y'
1324     And     NVL(AID.reversal_flag, 'N') <> 'Y'
1325     And     AID.invoice_id = p_invoice_id
1326     And     AID.invoice_line_number <> p_line_number
1327     And     AID.charge_applicable_to_dist_id IS NOT NULL
1328     And     AID.charge_applicable_to_dist_id In
1329            (Select AID2.invoice_distribution_id
1330             From ap_invoice_distributions_all AID2
1331             Where AID2.invoice_id = p_Invoice_Id
1332             And AID2.invoice_line_number = p_Line_Number
1333             And NVL(AID2.cancellation_flag, 'N') <> 'Y'
1334             And NVL(AID2.reversal_flag, 'N') <> 'Y' );
1335 
1336     If (dummy >= 1) Then
1337       return  TRUE;
1338     End if;
1339 
1340     return FALSE;
1341 
1342   Exception
1343     WHEN OTHERS THEN
1344       If (SQLCODE <> -20001) Then
1345         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1346         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1347         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1348         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1349                               ||', line number = '|| p_Line_Number);
1350         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1351       End If;
1352       APP_EXCEPTION.RAISE_EXCEPTION;
1353   End Line_Dists_Referred_By_Other;
1354 
1355  /*=============================================================================
1356  |  Public FUNCTION Outstanding_Alloc_Exists
1357  |
1358  |      Check if the particular invoice line contains outstanding allocation
1359  |      rule exists (not yet applied)
1360  |
1361  |  PROGRAM FLOW
1362  |
1363  |       return TRUE  - if line contains outstanding allocations
1364  |       return FALSE - otherwise.
1365  |
1366  |  MODIFICATION HISTORY
1367  |  Date         Author               Description of Change
1368  |  03/10/13     bghose               Created
1369  *============================================================================*/
1370 
1371   FUNCTION Outstanding_Alloc_Exists (p_Invoice_Id        Number,
1372                             p_Line_Number       Number,
1373                             p_Calling_Sequence  Varchar2) Return Boolean Is
1374     dummy number := 0;
1375     current_calling_sequence   Varchar2(2000);
1376     debug_info                           Varchar2(100);
1377 
1378   Begin
1379     -- Update the calling sequence
1380     --
1381     current_calling_sequence :=
1382                'AP_INVOICE_LINES_UTILITY_PKG.Outstanding_Alloc_Exists <-'||
1383                             p_Calling_Sequence;
1384     debug_info := 'Select from ap_allocatin_rules';
1385 
1386     Select count(*)
1387     Into   dummy
1388     From   ap_allocation_rules  AR,
1389            ap_allocation_rule_lines ARL
1390     Where  AR.invoice_id = p_Invoice_Id
1391     And    AR.invoice_id = ARL.invoice_id (+)
1392     And    AR.chrg_invoice_line_number = ARL.chrg_invoice_line_number (+)
1393     And    ARL.to_invoice_line_number (+)  = p_line_number
1394     And    AR.status = 'PENDING';
1395 
1396     If (dummy >= 1) Then
1397       return  TRUE;
1398     End if;
1399 
1400     return FALSE;
1401   Exception
1402     WHEN OTHERS THEN
1403       If (SQLCODE <> -20001) Then
1404         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1405         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1406         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1407         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1408                               ||', line number = '|| p_Line_Number);
1409         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1410       End If;
1411       APP_EXCEPTION.RAISE_EXCEPTION;
1412   End Outstanding_Alloc_Exists;
1413 
1414  /*=============================================================================
1415  |  Public FUNCTION Line_Dists_Trans_Pa
1416  |
1417  |      Check if the particular invoice line contains project related
1418  |      distributions
1419  |
1420  |  PROGRAM FLOW
1421  |
1422  |       return TRUE  - if line has been referred by any correction
1423  |       return FALSE - otherwise.
1424  |
1425  |  MODIFICATION HISTORY
1426  |  Date         Author               Description of Change
1427  |  03/10/13     bghose               Created
1428  *============================================================================*/
1429 
1430   FUNCTION Line_Dists_Trans_Pa (p_Invoice_Id        Number,
1431                             p_Line_Number       Number,
1432                             p_Calling_Sequence  Varchar2) Return Boolean Is
1433     dummy number := 0;
1434     current_calling_sequence   Varchar2(2000);
1435     debug_info                 Varchar2(100);
1436 
1437   Begin
1438     -- Update the calling sequence
1439     --
1440     current_calling_sequence :=
1441                'AP_INVOICE_LINES_UTILITY_PKG.Line_Dists_Trans_PA <-'||
1442                             p_Calling_Sequence;
1443     debug_info := 'Select from ap_invoic_distributions_all';
1444 
1445     Select count(*)
1446     Into   dummy
1447     From   ap_invoice_distributions_all
1448     Where invoice_id = p_Invoice_Id
1449     And invoice_line_number = p_Line_Number
1450     And pa_addition_flag In ('T', 'Y', 'Z') ;
1451 
1452     If (dummy >= 1) Then
1453       return  TRUE;
1454     End if;
1455 
1456     return FALSE;
1457 
1458   Exception
1459     WHEN OTHERS THEN
1460       If (SQLCODE <> -20001) Then
1461         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1462         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1463         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1464         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1465                               ||', line number = '|| p_Line_Number);
1466         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1467       End If;
1468       APP_EXCEPTION.RAISE_EXCEPTION;
1469   End Line_Dists_Trans_Pa;
1470 
1471  /*=============================================================================
1472  |  Public FUNCTION Can_Line_Be_Deleted
1473  |
1474  |      Check if the particular invoice line can be deleted
1475  |
1476  |  PROGRAM FLOW
1477  |
1478  |       return TRUE  - if line can be deleted
1479  |       return FALSE - otherwise and return error code.
1480  |
1481  |  MODIFICATION HISTORY
1482  |  Date         Author               Description of Change
1483  |  03/10/13     bghose               Created
1484  *============================================================================*/
1485 
1486   FUNCTION Can_Line_Be_Deleted (p_line_rec    IN ap_invoice_lines%ROWTYPE,
1487                               p_error_code  OUT NOCOPY Varchar2,
1488                               p_Calling_Sequence  Varchar2) Return Boolean Is
1489     current_calling_sequence   Varchar2(2000);
1490 
1491   Begin
1492     -- Update the calling sequence
1493     --
1494     current_calling_sequence :=
1495                'AP_INVOICE_LINES_UTILITY_PKG.Can_Line_Be_Deleted <-'||
1496                             p_Calling_Sequence;
1497 
1498     If (Ap_Invoice_Lines_Utility_Pkg.Line_Dists_Acct_Event_Created
1499                                    (p_Line_Rec.Invoice_Id,
1500                                     p_Line_Rec.Line_Number,
1501                                     Current_calling_sequence) = TRUE)  Then
1502        p_error_code := 'AP_INV_LINE_DELETE_VALIDATED';
1503        return False;
1504     ElsIf (Ap_Invoice_Lines_Utility_Pkg.Line_Referred_By_Corr
1505                                    (p_Line_Rec.Invoice_Id,
1506                                     p_Line_Rec.Line_Number,
1507                                     Current_calling_sequence) = TRUE)  Then
1508        p_error_code := 'AP_INV_LINE_DELETE_CORR';
1509        return False;
1510     ElsIf (NVL(Ap_Invoice_Lines_Utility_Pkg.Get_Encumbered_Flag
1511                                    (p_Line_Rec.Invoice_Id,
1512                                     p_Line_Rec.Line_Number), 'N')
1513                                        In ('Y', 'P'))  Then
1514        p_error_code := 'AP_INV_LINE_DELETE_ENCUMBERED';
1515        return False;
1516     ElsIf (Ap_Invoice_Lines_Utility_Pkg.Get_Posting_Status
1517                                    (p_Line_Rec.Invoice_Id,
1518                                     p_Line_Rec.Line_Number)
1519                                        In ('Y', 'P', 'S'))  Then
1520        p_error_code := 'AP_INV_LINE_DELETE_ACCOUNTED';
1521        return False;
1522     ElsIf (Ap_Invoice_Lines_Utility_Pkg.Line_Dists_Trans_PA
1523                                    (p_Line_Rec.Invoice_Id,
1524                                     p_Line_Rec.Line_Number,
1525                                     Current_calling_sequence) = TRUE)  Then
1526        p_error_code := 'AP_INV_LINE_DELETE_PA';
1527        return False;
1528     ElsIf (Ap_Invoice_Lines_Utility_Pkg.Line_Dists_Referred_By_Other
1529                                    (p_Line_Rec.Invoice_Id,
1530                                     p_Line_Rec.Line_Number,
1531                                     Current_calling_sequence) = TRUE)  Then
1532        p_error_code := 'AP_INV_LINE_REF_BY_DISTS';
1533        return False;
1534     ElsIf (Ap_Invoice_Lines_Utility_Pkg.Outstanding_Alloc_Exists
1535                                    (p_Line_Rec.Invoice_Id,
1536                                     p_Line_Rec.Line_Number,
1537                                     Current_calling_sequence) = TRUE)  Then
1538        p_error_code := 'AP_INV_LINE_HAS_ALLOC_RULE';
1539        return False;
1540     End If;
1541 
1542     p_error_code := null;
1543     return TRUE;
1544 
1545   Exception
1546     WHEN OTHERS THEN
1547       If (SQLCODE <> -20001) Then
1548         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1549         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1550         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1551         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||
1552                                 p_line_rec.Invoice_id
1553                               ||', line number = '|| p_line_rec.Line_Number);
1554       End If;
1555       APP_EXCEPTION.RAISE_EXCEPTION;
1556   End Can_Line_Be_Deleted;
1557 
1558  /*=============================================================================
1559  |  Public FUNCTION Get_Packet_Id
1560  |
1561  |      Get the Packet Id for a line
1562  |
1563  |  PROGRAM FLOW
1564  |
1565  |
1566  |  MODIFICATION HISTORY
1567  |  Date         Author               Description of Change
1568  |  03/10/13     bghose               Created
1569  *============================================================================*/
1570 
1571   FUNCTION Get_Packet_Id (p_invoice_id In Number,
1572                           p_Line_Number In Number)    Return Number Is
1573 
1574     l_packet_id number := '';
1575     Cursor packet_id_cursor Is
1576     Select decode(count(distinct(packet_id)),1,max(packet_id),'')
1577     From ap_invoice_distributions
1578     Where invoice_id = p_Invoice_Id
1579     And invoice_line_number = p_Line_Number
1580     And packet_id is not null;
1581 
1582     Begin
1583       Open packet_id_cursor;
1584       Fetch packet_id_cursor INTO l_packet_id;
1585       Close packet_id_cursor;
1586 
1587     Return(l_packet_id);
1588   End get_packet_id;
1589 
1590 
1591 /*=============================================================================
1592  |  FUNCTION - Is_Line_Fully_Distributed
1593  |
1594  |  DESCRIPTION
1595  |    This function returns TRUE if the line is completelly distributed.
1596  |    It returns FALSE otherwise.
1597  |
1598  |  PARAMETERS
1599  |      P_Invoice_Id - Invoice Id
1600  |      P_Line_number - line number
1601  |      P_Calling_Sequence - debug usage
1602  |
1603  |  KNOWN ISSUES:
1604  |
1605  |  NOTES:
1606  |
1607  |  MODIFICATION HISTORY
1608  |  Date         Author             Description of Change
1609  |  30-JUL-2003  SYIDNER            Creation
1610  |
1611  *============================================================================*/
1612 
1613   FUNCTION Is_Line_Fully_Distributed(
1614              P_Invoice_Id           IN NUMBER,
1615              P_Line_Number          IN NUMBER,
1616              P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN
1617 
1618   IS
1619 
1620   CURSOR Dist_Var_Cur IS
1621     SELECT 'Dist Total <> Invoice Line Amount'
1622     FROM   ap_invoice_lines AIL, ap_invoice_distributions D
1623     WHERE  AIL.invoice_id  = D.invoice_id
1624     AND    AIL.line_number = p_line_number
1625     AND    AIL.invoice_id  = p_invoice_id
1626     AND    AIL.line_number = D.invoice_line_number
1627     AND    (D.line_type_lookup_code <> 'RETAINAGE'
1628     	    OR (AIL.line_type_lookup_code = 'RETAINAGE RELEASE'
1629     	        and D.line_type_lookup_code = 'RETAINAGE'))
1630     AND    (AIL.line_type_lookup_code <> 'ITEM'
1631             or (AIL.line_type_lookup_code = 'ITEM'
1632                 and (D.prepay_distribution_id IS NULL
1633                      or (D.prepay_distribution_id IS NOT NULL
1634                          and D.line_type_lookup_code NOT IN ('PREPAY', 'REC_TAX', 'NONREC_TAX')))))
1635     GROUP BY AIL.invoice_id, AIL.line_number, AIL.amount
1636     HAVING AIL.amount <> nvl(SUM(nvl(D.amount,0)),0);
1637 
1638     current_calling_sequence   VARCHAR2(4000);
1639     debug_info                 VARCHAR2(240);
1640     l_test_var                 VARCHAR2(50);
1641 
1642   BEGIN
1643       -------------------------------------------------------------
1644       current_calling_sequence := 'AP_INVOICE_LINES_UTILITY_PKG - Is_Line_Fully_Distributed';
1645       debug_info := 'Is_Line_Fully_Distributed - Open cursor';
1646       -------------------------------------------------------------
1647 
1648       OPEN  Dist_Var_Cur;
1649       FETCH Dist_Var_Cur
1650        INTO l_test_var;
1651       CLOSE Dist_Var_Cur;
1652 
1653       RETURN (l_test_var IS NULL);
1654 
1655   EXCEPTION
1656     WHEN OTHERS THEN
1657       IF (SQLCODE <> -20001) then
1658         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1659         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1660         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1661         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||P_Invoice_Id);
1662         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1663       END IF;
1664 
1665       IF (Dist_Var_Cur%ISOPEN) THEN
1666         CLOSE Dist_Var_Cur;
1667       END IF;
1668 
1669       APP_EXCEPTION.RAISE_EXCEPTION;
1670 
1671   END Is_Line_Fully_Distributed;
1672 
1673 /*=============================================================================
1674  |  FUNCTION - Is_PO_RCV_Amount_Exceeded
1675  |
1676  |  DESCRIPTION
1677  |    This function returns TRUE if the reversal of the line makes the
1678  |    quantity or amount billed go below 0.  It returns FALSE otherwise.
1679  |
1680  |  PARAMETERS
1681  |      P_Invoice_Id - Invoice Id
1682  |      P_Line_Number - line number
1683  |      P_Calling_Sequence - debug usage
1684  |
1685  |  KNOWN ISSUES:
1686  |
1687  |  NOTES:
1688  |
1689  |  MODIFICATION HISTORY
1690  |  Date         Author             Description of Change
1691  |  30-JUL-2003  SYIDNER            Creation
1692  |
1693  *============================================================================*/
1694 
1695   FUNCTION Is_PO_RCV_Amount_Exceeded(
1696              P_Invoice_Id           IN NUMBER,
1697              P_Line_Number          IN NUMBER,
1698              P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN
1699 
1700   IS
1701     CURSOR Invoice_Validation IS
1702     SELECT count(*)
1703       FROM po_distributions_all POD,
1704            ap_invoice_distributions AID
1705      WHERE POD.po_distribution_id = AID.po_distribution_id
1706        AND AID.invoice_id = P_Invoice_Id
1707        AND POD.org_id = AID.org_id
1708        AND AID.invoice_line_number = P_Line_Number
1709        AND NVL(AID.reversal_flag,'N')<>'Y'
1710        AND ( NVL(POD.quantity_billed, 0) -
1711              decode( AID.dist_match_type,
1712                      'PRICE_CORRECTION',  0,
1713                      'AMOUNT_CORRECTION', 0,    /* Ampunt Based Matching */
1714                      'ITEM_TO_SERVICE_PO', 0,
1715                      'ITEM_TO_SERVICE_RECEIPT', 0,
1716                      nvl( AID.corrected_quantity,0 ) +
1717                      nvl( AID.quantity_invoiced,0 ) ) < 0
1718              OR
1719              NVL(POD.amount_billed, 0) - NVL(AID.amount, 0) < 0 );
1720 
1721     l_invoice_id               ap_invoices_all.invoice_id%TYPE;
1722     current_calling_sequence   VARCHAR2(4000);
1723     debug_info                 VARCHAR2(240);
1724     l_po_dist_count            NUMBER := 0;
1725     l_return_var               BOOLEAN := FALSE;
1726 
1727 
1728   BEGIN
1729       current_calling_sequence := 'AP_INVOICE_LINES_UTILITY_PKG - Is_PO_RCV_Amount_Exceeded';
1730       -------------------------------------------------------------
1731       debug_info := 'Is_PO_RCV_Amount_Exceeded - Open cursor';
1732       -------------------------------------------------------------
1733 
1734       OPEN invoice_validation;
1735       FETCH invoice_validation INTO l_po_dist_count;
1736       CLOSE invoice_validation;
1737 
1738       -------------------------------------------------------------
1739       debug_info := 'Check if quantity_billed on po_distribution is
1740                      brought to 0';
1741       -------------------------------------------------------------
1742       IF (l_po_dist_count > 0  ) THEN
1743         l_return_var := TRUE;
1744       END IF;
1745 
1746     RETURN l_return_var;
1747 
1748   EXCEPTION
1749     WHEN OTHERS THEN
1750       if (SQLCODE <> -20001) then
1751         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1752         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1753         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1754         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||P_Invoice_Id);
1755         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1756       end if;
1757       debug_info := debug_info || 'Error occurred';
1758 
1759       IF ( invoice_validation%ISOPEN ) THEN
1760         CLOSE invoice_validation;
1761       END IF;
1762 
1763       APP_EXCEPTION.RAISE_EXCEPTION;
1764 
1765   END Is_PO_RCV_Amount_Exceeded;
1766 
1767  /*=============================================================================
1768  |  Public FUNCTION Is_Invoice_Fully_Distributed
1769  |
1770  |    Check if an invoice is fully distributed or not. An invoice is
1771  |    fully distributed if all of its lines were distributed.
1772  |
1773  |  PROGRAM FLOW
1774  |
1775  |       return TRUE  - if invoice is fully distributed
1776  |       return FALSE - otherwise.
1777  |
1778  |  MODIFICATION HISTORY
1779  |  Date          Author               Description of Change
1780  |  24-FEB-2004   ISartawi             Created
1781  *============================================================================*/
1782 
1783 FUNCTION Is_Invoice_Fully_Distributed (
1784           P_invoice_id  IN NUMBER) RETURN BOOLEAN
1785 IS
1786   l_count NUMBER;
1787 BEGIN
1788 
1789   -- This function is used to determine if the invoice is fully
1790   -- distributed or not. The invoice is fully distributed if all
1791   -- its lines were distributed. In this case the line will have
1792   -- generate_dists = 'D'. If one line had generate_dists <> 'D'
1793   -- then the invoice is not fully distributed.
1794 
1795   SELECT COUNT(*)
1796     INTO l_count
1797     FROM ap_invoice_lines
1798    WHERE invoice_id      = p_invoice_id
1799      AND generate_dists <> 'D'
1800      AND ROWNUM = 1;
1801 
1802   IF l_count > 0 THEN
1803     RETURN (FALSE);  -- The Invoice is not fully distributed
1804   ELSE
1805     RETURN (TRUE);   -- The Invoice is fully distributed
1806   END IF;
1807 
1808 END Is_Invoice_Fully_Distributed;
1809 
1810 
1811 --Invoice Lines: Distributions
1812 /*=============================================================================
1813 |  Public FUNCTION Pending_Alloc_Exists_Chrg_Line
1814 |
1815 |  Check if the particular invoice charge line contains outstanding allocation
1816 |      rule exists (not yest applied)
1817 |
1818 |  PROGRAM FLOW
1819 |
1820 |       return TRUE  - if line contains outstanding allocations
1821 |       return FALSE - otherwise.
1822 |
1823 |  MODIFICATION HISTORY
1824 |  Date           Author               Description of Change
1825 |  01/27/2004     surekha myadam       Created
1826 *============================================================================*/
1827   FUNCTION Pending_Alloc_Exists_Chrg_Line
1828                            (p_Invoice_Id        Number,
1829                             p_Line_Number       Number,
1830                             p_Calling_Sequence  Varchar2) Return Boolean Is
1831     dummy number := 0;
1832     current_calling_sequence   Varchar2(2000);
1833     debug_info                           Varchar2(100);
1834   Begin
1835     -- Update the calling sequence
1836     --
1837     current_calling_sequence :=
1838     'AP_INVOICE_LINES_UTILITY_PKG.Pending_Alloc_Exists_Chrg_Line <-'||
1839                             p_Calling_Sequence;
1840     debug_info := 'Select from ap_allocatin_rules';
1841 
1842     Select count(*)
1843     Into   dummy
1844     From   ap_allocation_rules  AR
1845     Where  AR.invoice_id = p_Invoice_Id
1846     And    AR.chrg_invoice_line_number = p_line_number
1847     And    AR.status = 'PENDING';
1848 
1849     If (dummy >= 1) Then
1850       return  TRUE;
1851     End if;
1852 
1853     return FALSE;
1854   Exception
1855     WHEN OTHERS THEN
1856       If (SQLCODE <> -20001) Then
1857         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
1858         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
1859         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1860         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||p_Invoice_id
1861                               ||', line number = '|| p_Line_Number);
1862         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
1863       End If;
1864       APP_EXCEPTION.RAISE_EXCEPTION;
1865 End Pending_Alloc_Exists_Chrg_Line;
1866 
1867 
1868 /*=============================================================================
1869 |  Public FUNCTION Is_Line_a_Correction
1870 |
1871 |  Check if the particular invoice line is correcting some other invoice line.
1872 |
1873 |  PROGRAM FLOW
1874 |
1875 |       return TRUE  - if line is a correction
1876 |       return FALSE - otherwise.
1877 |
1878 |  MODIFICATION HISTORY
1879 |  Date           Author               Description of Change
1880 |  01-JUL-2004    Surekha Myadam       Created
1881 *============================================================================*/
1882 FUNCTION Is_Line_a_Correction(
1883                 P_Invoice_Id           IN NUMBER,
1884 		P_Line_Number          IN NUMBER,
1885 		P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN IS
1886 
1887 is_correction varchar2(1) := 'N';
1888 BEGIN
1889 
1890    SELECT 'Y'
1891    INTO is_correction
1892    FROM ap_invoice_lines
1893    WHERE invoice_id = p_invoice_id
1894    AND line_number = p_line_number
1895    AND corrected_inv_id IS NOT NULL
1896    AND corrected_line_number IS NOT NULL;
1897 
1898 
1899    IF (is_correction = 'Y') THEN
1900     return (TRUE);
1901    ELSE
1902     return (FALSE);
1903    END IF;
1904 
1905 EXCEPTION WHEN OTHERS THEN
1906   RETURN(FALSE);
1907 
1908 END Is_Line_a_Correction;
1909 
1910 
1911 
1912 /*=============================================================================
1913 |  Public FUNCTION Line_Referred_By_Adjustment
1914 |
1915 |  Check if the particular invoice line has been adjusted by PO Price Adjustment
1916 |
1917 |  PROGRAM FLOW
1918 |
1919 |       return TRUE  - if line is adjusted by PO Price Adjustment
1920 |       return FALSE - otherwise.
1921 |
1922 |  MODIFICATION HISTORY
1923 |  Date           Author               Description of Change
1924 |  01-JUL-2004    Surekha Myadam       Created
1925 *============================================================================*/
1926 FUNCTION Line_Referred_By_Adjustment(
1927                 P_Invoice_Id           IN NUMBER,
1928                 P_Line_Number          IN NUMBER,
1929                 P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN IS
1930  l_count NUMBER := 0;
1931 BEGIN
1932 
1933   SELECT count(*)
1934   INTO l_count
1935   FROM ap_invoice_lines_all
1936   WHERE corrected_inv_id = p_invoice_id
1937   AND corrected_line_number = p_line_number
1938   AND line_type_lookup_code IN ('RETROITEM')
1939   AND line_source = 'PO PRICE ADJUSTMENT'
1940   AND match_type = 'RETRO PRICE ADJUSTMENT';
1941 
1942 
1943   IF (l_count > 0) THEN
1944     RETURN (TRUE);
1945   ELSE
1946     RETURN (FALSE);
1947   END IF;
1948 
1949 END Line_Referred_By_Adjustment;
1950 
1951 
1952 /*=============================================================================
1953 |  Public FUNCTION Is_Line_a_Adjustment
1954 |
1955 |  Check if the particular invoice line has adjusted (po price adjust)
1956 |  some other invoice line.
1957 |
1958 |  PROGRAM FLOW
1959 |
1960 |       return TRUE  - if line is a po price adjustment line.
1961 |       return FALSE - otherwise.
1962 |
1963 |  MODIFICATION HISTORY
1964 |  Date           Author               Description of Change
1965 |  01-JUL-2004    Surekha Myadam       Created
1966 *============================================================================*/
1967 FUNCTION Is_Line_a_Adjustment(
1968                 P_Invoice_Id           IN NUMBER,
1969                 P_Line_Number          IN NUMBER,
1970                 P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN IS
1971  is_po_price_adjustment VARCHAR2(1) := 'N';
1972 BEGIN
1973 
1974   SELECT 'Y'
1975   INTO is_po_price_adjustment
1976   FROM ap_invoice_lines_all
1977   WHERE invoice_id = p_invoice_id
1978   AND line_number = p_line_number
1979   AND line_type_lookup_code = 'RETROITEM'
1980   AND line_source = 'PO PRICE ADJUSTMENT'
1981   AND match_type = 'RETRO PRICE ADJUSTMENT';
1982 
1983   IF (is_po_price_adjustment = 'Y') THEN
1984     RETURN(TRUE);
1985   ELSE
1986     RETURN(FALSE);
1987   END IF;
1988 
1989  EXCEPTION WHEN OTHERS THEN
1990    RETURN(FALSE);
1991 
1992 END Is_Line_a_Adjustment;
1993 
1994 
1995 /*=============================================================================
1996 | Public FUNCTION Is_Line_a_Prepay
1997 |
1998 | Check if the particular invoice line is a prepayment application/unapplication
1999 |  (Normally this can be identified by looking at the line_type_lookup_code
2000 |   but from the place where this is called (etax windows) the line_type is not
2001 |   available, hence need to code this function.)
2002 |
2003 |  PROGRAM FLOW
2004 |
2005 |       return TRUE  - if line of type PREPAY.
2006 |       return FALSE - otherwise.
2007 |
2008 |  MODIFICATION HISTORY
2009 |  Date           Author               Description of Change
2010 |  01-JUL-2004    Surekha Myadam       Created
2011 *============================================================================*/
2012 FUNCTION Is_Line_a_Prepay(
2013                 P_Invoice_Id           IN NUMBER,
2014                 P_Line_Number          IN NUMBER,
2015                 P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN IS
2016  is_prepayment varchar2(1) := 'N';
2017 BEGIN
2018 
2019   SELECT 'Y'
2020   INTO is_prepayment
2021   FROM ap_invoice_lines
2022   WHERE invoice_id = p_invoice_id
2023   AND line_number = p_line_number
2024   AND line_type_lookup_code = 'PREPAY';
2025 
2026   IF (is_prepayment = 'Y') THEN
2027     return (TRUE);
2028   ELSE
2029     return (FALSE);
2030   END IF;
2031 
2032 EXCEPTION WHEN OTHERS THEN
2033 
2034   return(FALSE);
2035 
2036 END Is_Line_a_Prepay;
2037 
2038 Function Get_Retained_Amount
2039 		(p_line_location_id IN NUMBER,
2040 		 p_match_amount	    IN NUMBER) RETURN NUMBER IS
2041 
2042   l_ret_status		Varchar2(100);
2043   l_msg_data		Varchar2(4000);
2044 
2045   l_currency_code       PO_HEADERS_ALL.currency_code%type;
2046 
2047   l_line_loc_tab	PO_TBL_NUMBER;
2048   l_line_loc_amt_tab	PO_TBL_NUMBER;
2049   l_amt_to_retain_tab	PO_TBL_NUMBER;
2050 
2051   l_retained_amount     Number;
2052 
2053 Begin
2054 
2055   If p_line_location_id Is Not Null Then
2056 
2057      l_line_loc_tab := po_tbl_number();
2058      l_line_loc_tab.extend;
2059      l_line_loc_tab(l_line_loc_tab.last) := p_line_location_id;
2060 
2061      l_line_loc_amt_tab := po_tbl_number();
2062      l_line_loc_amt_tab.extend;
2063      l_line_loc_amt_tab(l_line_loc_amt_tab.last) := p_match_amount;
2064 
2065      -- bug6882900
2066      BEGIN
2067 
2068 	SELECT currency_code
2069 	INTO l_currency_code
2070 	FROM po_headers_all
2071 	WHERE po_header_id IN
2072 	  (SELECT po_header_id
2073 	   FROM po_line_locations_all
2074 	   WHERE line_location_id = p_line_location_id)
2075 	AND rownum < 2;
2076 
2077      EXCEPTION
2078         WHEN OTHERS THEN
2079 	  NULL;
2080 
2081      END;
2082 
2083 
2084      PO_AP_INVOICE_MATCH_GRP.get_amount_to_retain(
2085 		  p_api_version			=> 1.0
2086 		, p_line_location_id_tbl        => l_line_loc_tab
2087 		, p_line_loc_match_amt_tbl      => l_line_loc_amt_tab
2088 		, x_return_status		=> l_ret_status
2089 		, x_msg_data                    => l_msg_data
2090 		, x_amount_to_retain_tbl        => l_amt_to_retain_tab);
2091 
2092      IF l_amt_to_retain_tab.count > 0 THEN
2093 
2094         l_retained_amount := -1 * l_amt_to_retain_tab(l_amt_to_retain_tab.last);
2095 
2096      END IF;
2097 
2098   End If;
2099 
2100   -- bug6882900
2101   Return (ap_utilities_pkg.ap_round_currency(l_retained_amount, l_currency_code));
2102 
2103 End Get_Retained_Amount;
2104 
2105 /* ==========================================================================================
2106  *  Procedure manual_withhold_tax()
2107  *  Objective update ap_payment_schedules.remaining_amount for manual entry
2108  *  withholding lines
2109  *  This procedire has been moved from payment schedules library since it did
2110  *  not consider the
2111  *  ap lines model
2112  *  This PROCEDURE is added for Bug 6917289
2113  * =============================================================================================*/
2114 PROCEDURE Manual_Withhold_Tax(p_invoice_id IN number
2115                              ,p_manual_withhold_amount IN number
2116                              ) IS
2117 
2118  l_inv_amt_remaining  ap_payment_schedules.amount_remaining%TYPE := 0;
2119  l_gross_amount       ap_payment_schedules.gross_amount%TYPE := 0;
2120  l_payment_cross_rate ap_invoices_all.payment_cross_rate%TYPE :=0;
2121  l_payment_currency_code ap_invoices_all.payment_currency_code%TYPE;
2122 
2123  -- Debug variables
2124  l_debug_loc                   VARCHAR2(30) := 'Manual_Withhold_Tax';
2125  l_curr_calling_sequence       VARCHAR2(2000);
2126  l_debug_info                  VARCHAR2(2000);
2127 
2128 
2129 BEGIN
2130 
2131   l_curr_calling_sequence := 'AP_INVOICE_LINES_UTILITY_PKG.'||l_debug_loc;
2132 
2133   SELECT nvl(payment_cross_rate,0), payment_currency_code
2134     INTO l_payment_cross_rate, l_payment_currency_code
2135     FROM ap_invoices_all
2136    WHERE invoice_id = p_invoice_id;
2137 
2138   SELECT sum(nvl(amount_remaining,0)), sum(nvl(gross_amount,0))
2139     INTO l_inv_amt_remaining, l_gross_amount
2140     FROM ap_payment_schedules
2141    WHERE invoice_id = p_invoice_id;
2142 
2143   l_debug_info := 'Updating payment schedules due a manual withholding tax';
2144 
2145   IF ((l_inv_amt_remaining <> 0) AND (p_manual_withhold_amount is not null))
2146   THEN
2147           update ap_payment_schedules
2148              set amount_remaining = (amount_remaining +
2149                                      ap_utilities_pkg.ap_round_currency(
2150                         (amount_remaining * (p_manual_withhold_amount/l_inv_amt_remaining)
2151                          * l_payment_cross_rate), l_payment_currency_code))
2152            where invoice_id = p_invoice_id;
2153 
2154   ELSIF ((l_inv_amt_remaining = 0) and (p_manual_withhold_amount is not null))
2155      THEN
2156           update ap_payment_schedules
2157              set amount_remaining = (amount_remaining +
2158                                      ap_utilities_pkg.ap_round_currency(
2159                      (gross_amount * (p_manual_withhold_amount/l_gross_amount)
2160                       * l_payment_cross_rate), l_payment_currency_code)),
2161                  payment_status_flag = DECODE(payment_status_flag,'Y','P',payment_status_flag)
2162            where invoice_id = p_invoice_id;
2163 
2164           update ap_invoices
2165              set payment_status_flag = DECODE(payment_status_flag,'Y','P',payment_status_flag)
2166            where invoice_id = p_invoice_id ;
2167 
2168   END IF;
2169 
2170 EXCEPTION
2171   WHEN NO_DATA_FOUND THEN
2172        NULL;
2173   WHEN OTHERS THEN
2174        IF (SQLCODE <> -20001) THEN
2175            FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
2176            FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
2177            FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
2178            FND_MESSAGE.SET_TOKEN('PARAMETERS',
2179                           'P_Invoice_Id  = '|| p_invoice_id
2180                       ||', p_manual_withhold_amount= '|| to_char(p_manual_withhold_amount));
2181            FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
2182        END IF;
2183 
2184        APP_EXCEPTION.RAISE_EXCEPTION;
2185 
2186 END Manual_Withhold_Tax;
2187 
2188 /* ==================================================================================
2189  *  Function get_awt_flag()
2190  *  Objective Retrun the awt_flag for a given invoice_id and invoice_line_number
2191  *  This function is called from the invoice lines library
2192  *  Bug 6917289
2193  * ==================================================================================*/
2194 
2195 FUNCTION get_awt_flag(
2196              p_invoice_id  IN  NUMBER,
2197              p_line_number IN  NUMBER )
2198   RETURN VARCHAR2
2199   IS
2200       l_awt_flag ap_invoice_distributions_all.awt_flag%TYPE;
2201 
2202 BEGIN
2203 
2204   SELECT awt_flag
2205     INTO l_awt_flag
2206     FROM ap_invoice_distributions_all
2207    WHERE invoice_id = p_invoice_id
2208      AND invoice_line_number = p_line_number
2209      AND rownum = 1;
2210 
2211   IF l_awt_flag is null THEN
2212      RETURN ('Z');
2213   ELSE
2214      RETURN (l_awt_flag);
2215   END IF;
2216 
2217 EXCEPTION
2218   WHEN NO_DATA_FOUND THEN
2219        RETURN ('B');
2220   WHEN Others THEN
2221        RETURN ('Z');
2222 END get_awt_flag;
2223 
2224 END  AP_INVOICE_LINES_UTILITY_PKG;