DBA Data[Home] [Help]

PACKAGE BODY: APPS.AP_INVOICES_UTILITY_PKG

Source


1 PACKAGE BODY AP_INVOICES_UTILITY_PKG AS
2 /* $Header: apinvutb.pls 120.56.12010000.5 2008/11/14 12:49:04 sbonala ship $ */
3 
4 /*=============================================================================
5  |  FUNCTION - get_prepay_number
6  |
7  |  DESCRIPTION
8  |      returns the prepayment number that the prepayment distribution  is
9  |      associated with.
10  |
11  |  KNOWN ISSUES:
12  |
13  |  NOTES:
14  |
15  |  MODIFICATION HISTORY
16  |  Date         Author             Description of Change
17  |
18  *============================================================================*/
19 
20     FUNCTION get_prepay_number (l_prepay_dist_id IN NUMBER)
21     RETURN VARCHAR2 IS
22       l_prepay_number VARCHAR2(50);
23 
24       CURSOR c_prepay_number IS
25       SELECT invoice_num
26       FROM   ap_invoices
27       WHERE invoice_id =
28                 (SELECT invoice_id
29                    FROM ap_invoice_distributions
30                   WHERE invoice_distribution_id = l_prepay_dist_id);
31     BEGIN
32 
33       OPEN  c_prepay_number;
34       FETCH c_prepay_number
35       INTO  l_prepay_number;
36       CLOSE c_prepay_number;
37 
38       RETURN(l_prepay_number);
39 
40     END get_prepay_number;
41 
42 /*=============================================================================
43  |  FUNCTION - get_prepay_dist_number
44  |
45  |  DESCRIPTION
46  |      Returns the distribution_line_number that the prepayment associated
47  |      with.
48  |
49  |  KNOWN ISSUES:
50  |
51  |  NOTES:
52  |
53  |  MODIFICATION HISTORY
54  |  Date         Author             Description of Change
55  |
56  *============================================================================*/
57 
58     FUNCTION get_prepay_dist_number (l_prepay_dist_id IN NUMBER)
59     RETURN VARCHAR2 IS
60       l_prepay_dist_number VARCHAR2(50);
61 
62       CURSOR c_prepay_dist_number IS
63       SELECT distribution_line_number
64       FROM   ap_invoice_distributions
65       WHERE  invoice_distribution_id = l_prepay_dist_id;
66 
67     BEGIN
68 
69       OPEN c_prepay_dist_number;
70       FETCH c_prepay_dist_number
71       INTO l_prepay_dist_number;
72       CLOSE c_prepay_dist_number;
73 
74       RETURN(l_prepay_dist_number);
75 
76     END get_prepay_dist_number;
77 
78 /*=============================================================================
79  |  FUNCTION - get_distribution_total
80  |
81  |  DESCRIPTION
82  |      returns the total distribution amount for the invoice.
83  |
84  |  KNOWN ISSUES:
85  |
86  |  NOTES:
87  |      1. Bug 1121323. Excluding the tax on the prepayment from the
88  |         distribution total.
89  |      2. Bug 1639039. Including the Prepayment and Prepayment Tax from
90  |         the distribution total if the invoice_includes_prepay_flag is
91  |         set to Y
92  |
93  |  MODIFICATION HISTORY
94  |  Date         Author             Description of Change
95  |
96  *============================================================================*/
97 
98     FUNCTION get_distribution_total(
99                   l_invoice_id IN NUMBER
100                        )
101     RETURN NUMBER IS
102 
103       distribution_total NUMBER := 0;
104       --Bugfix:3854385
105       l_Y	VARCHAR2(1) := 'Y';
106 
107     BEGIN
108 
109        -- eTax Uptake.  Modified to exclude REC_TAX and NONREC_TAX
110        -- distributions created for prepayment applications
111        SELECT SUM(NVL(aid.amount,0))
112          INTO distribution_total
113          FROM ap_invoice_distributions_all aid,
114               ap_invoice_lines_all ail
115         WHERE ail.invoice_id = l_invoice_id
116           AND aid.invoice_id = ail.invoice_id
117           AND aid.invoice_line_number = ail.line_number
118           AND ((aid.line_type_lookup_code NOT IN ('PREPAY', 'AWT')
119                 AND aid.prepay_distribution_id IS NULL)
120               OR NVL(ail.invoice_includes_prepay_flag,'N') = l_y);
121 
122 
123       RETURN(distribution_total);
124 
125     END get_distribution_total;
126 
127 
128 /*===========================================================================
129  |  FUNCTION -  get_posting_status
130  |
131  |  DESCRIPTION
132  |      returns the invoice posting status flag.
133  |
134  |  KNOWN ISSUES:
135  |
136  |  NOTES
137  |      'Y' - Posted
138  |      'N' - Unposted
139  |      'S' - Selected
140  |      'P' - Partially Posted
141  |      ---------------------------------------------------------------------
142  |      -- Declare cursor to establish the invoice-level posting flag
143  |      --
144  |      -- The first two selects simply look at the posting flags. The 'S'
145  |      -- one means the invoice distributions are selected for accounting
146  |      -- processing. The 'P' is to cover one specific case when some of
147  |      -- the distributions are fully posting (Y) and some are unposting (N).
148  |      -- The status should be partial (P).
149  |      --
150  |      -- MOAC.  Use ap_invoice_distributions_all table instead of SO view
151  |      -- since this procedure is called when policy context is not set to
152  |      -- the corresponding OU for the invoice_id
153  |
154  |  MODIFICATION HISTORY
155  |  Date         Author             Description of Change
156  |  04-Mar-05    Yicao              Rewrite the procedure for SLA project
157  *==========================================================================*/
158   FUNCTION get_posting_status(l_invoice_id IN NUMBER)
159     RETURN VARCHAR2 IS
160       invoice_posting_flag           VARCHAR2(1);
161       distribution_posting_flag      VARCHAR2(1);
162       l_cash_basis_flag              VARCHAR2(1);
163       l_org_id                       AP_SYSTEM_PARAMETERS_ALL.ORG_ID%TYPE;
164 
165 
166       CURSOR posting_cursor IS
167       SELECT cash_posted_flag
168       FROM   ap_invoice_distributions_all
169       WHERE  invoice_id = l_invoice_id
170       AND    l_cash_basis_flag = 'Y'
171       UNION
172       SELECT accrual_posted_flag
173       FROM   ap_invoice_distributions_all
174       WHERE  invoice_id = l_invoice_id
175       AND    l_cash_basis_flag <>'Y'
176       UNION
177       SELECT 'P'
178       FROM   ap_invoice_distributions_all
179       WHERE  invoice_id = l_invoice_id
180       AND  ((cash_posted_flag = 'Y'
181              AND l_cash_basis_flag = 'Y')
182       OR
183            (accrual_posted_flag = 'Y'
184             AND l_cash_basis_flag <> 'Y'))
185       AND EXISTS
186                (SELECT 'An N is also in the valid flags'
187                 FROM   ap_invoice_distributions_all
188                 WHERE  invoice_id = l_invoice_id
189                 AND    ((cash_posted_flag = 'N'
190                          AND l_cash_basis_flag = 'Y')
191                 OR
192                        (accrual_posted_flag = 'N'
193                          AND l_cash_basis_flag <> 'Y'))) -- bug fix 6975868;
194      -- bug fix 6975868  begin
195       UNION
196       SELECT cash_posted_flag
197       FROM   ap_self_assessed_tax_dist_all
198       WHERE  invoice_id = l_invoice_id
199       AND    l_cash_basis_flag = 'Y'
200       UNION
201       SELECT accrual_posted_flag
202       FROM   ap_self_assessed_tax_dist_all
203       WHERE  invoice_id = l_invoice_id
204       AND    l_cash_basis_flag <>'Y'
205       UNION
206       SELECT 'P'
207       FROM   ap_self_assessed_tax_dist_all
208       WHERE  invoice_id = l_invoice_id
209       AND  ((cash_posted_flag = 'Y'
210              AND l_cash_basis_flag = 'Y')
211       OR
212            (accrual_posted_flag = 'Y'
213             AND l_cash_basis_flag <> 'Y'))
214       AND EXISTS
215                (SELECT 'An N is also in the valid flags'
216                 FROM   ap_self_assessed_tax_dist_all
217                 WHERE  invoice_id = l_invoice_id
218                 AND    ((cash_posted_flag = 'N'
219                          AND l_cash_basis_flag = 'Y')
220                 OR
221                        (accrual_posted_flag = 'N'
222                          AND l_cash_basis_flag <> 'Y')));
223 
224      -- bug fix 6975868  end
225     BEGIN
226 
227     /*-----------------------------------------------------------------+
228     |  Get Accounting Methods                                          |
229     |  MOAC.  Added org_id to select statement.                        |
230     +-----------------------------------------------------------------*/
231 
232       SELECT nvl(sob.sla_ledger_cash_basis_flag, 'N'),
233              asp.org_id
234       INTO   l_cash_basis_flag,
235              l_org_id
236       FROM ap_invoices_all ai,
237            ap_system_parameters_all asp,
238            gl_sets_of_books sob
239       WHERE ai.invoice_id = l_invoice_id
240       AND ai.org_id = asp.org_id
241       AND asp.set_of_books_id = sob.set_of_books_id;
242 
243       invoice_posting_flag := 'X';
244 
245       OPEN posting_cursor;
246 
247       LOOP
248       FETCH posting_cursor INTO distribution_posting_flag;
249       EXIT WHEN posting_cursor%NOTFOUND;
250 
251         IF (distribution_posting_flag = 'S') THEN
252           invoice_posting_flag := 'S';
253         ELSIF (distribution_posting_flag = 'P' AND
254                invoice_posting_flag <> 'S') THEN
255           invoice_posting_flag := 'P';
256         ELSIF (distribution_posting_flag = 'N' AND
257                invoice_posting_flag NOT IN ('S','P')) THEN
258           invoice_posting_flag := 'N';
259 	ELSIF (distribution_posting_flag IS NULL) THEN
260           invoice_posting_flag := 'N';
261         END IF;
262 
263         IF (invoice_posting_flag NOT IN ('S','P','N')) THEN
264           invoice_posting_flag := 'Y';
265         END IF;
266       END LOOP;
267       CLOSE posting_cursor;
268 
269       if (invoice_posting_flag = 'X') then
270         invoice_posting_flag := 'N';
271       end if;
272 
273       --bug6160540
274       if invoice_posting_flag = 'N' then
275 
276          BEGIN
277           SELECT 'D'
278           INTO   invoice_posting_flag
279           FROM   ap_invoice_distributions_all AID,
280                   xla_events                   XE
281           WHERE  AID.invoice_id = l_invoice_id
282           AND    AID.accounting_event_id = XE.event_id
283           AND    ((AID.accrual_posted_flag = 'N' AND l_cash_basis_flag = 'N') OR
284                   (AID.cash_posted_flag = 'N' AND l_cash_basis_flag  = 'Y'))
285           AND    XE.process_status_code = 'D'
286           AND    rownum < 2;
287         EXCEPTION
288            WHEN OTHERS THEN
289               NULL;
290        END;
291 
292      end if;
293 
294      RETURN(invoice_posting_flag);
295     END get_posting_status;
296 
297 /*=============================================================================
298  |  FUNCTION -  CHECK_UNIQUE
299  |
300  |  DESCRIPTION
301  |      Check if the invoice number within one vendor is unique.
302  |
303  |  KNOWN ISSUES:
304  |
305  |  NOTES
306  |  MODIFICATION HISTORY
307  |  Date         Author             Description of Change
308  |
309  *============================================================================*/
310 
311     PROCEDURE CHECK_UNIQUE (
312                   X_ROWID             VARCHAR2,
313                   X_INVOICE_NUM       VARCHAR2,
314                   X_VENDOR_ID         NUMBER,
315                   X_ORG_ID            NUMBER,   -- Bug 5407785
316                   X_calling_sequence  IN VARCHAR2) IS
317 
318       dummy_a number := 0;
319       dummy_b number := 0;
320       current_calling_sequence    VARCHAR2(2000);
321       debug_info                  VARCHAR2(100);
322 
323     BEGIN
324 
325       current_calling_sequence := 'AP_INVOICES_UTILITY_PKG.CHECK_UNIQUE<-'||
326                                   X_calling_sequence;
327 
328       debug_info := 'Count for same vendor_id and invoice_num';
329 
330       select count(1)
331       into   dummy_a
332       from   ap_invoices_all
333       where  invoice_num = X_INVOICE_NUM
334       and    vendor_id = X_VENDOR_ID
335       and    org_id    = X_ORG_ID   -- Bug 5407785
336       and    ((X_ROWID is null) or (rowid <> X_ROWID));
337 
338       if (dummy_a >= 1) then
339         fnd_message.set_name('SQLAP','AP_ALL_DUPLICATE_VALUE');
340         app_exception.raise_exception;
341       end if;
342 
343       debug_info := 'Count for same vendor_id, invoice_num amount purged invoices';
344 
345       select count(1)
346       into   dummy_b
347       from   ap_history_invoices_all
348       where  invoice_num = X_INVOICE_NUM
349       and    vendor_id = X_VENDOR_ID   -- Bug 5407785
350       and    org_id    = X_ORG_ID;
351 
352       if (dummy_b >= 1) then
353         fnd_message.set_name('SQLAP','AP_ALL_DUPLICATE_VALUE');
354         app_exception.raise_exception;
355       end if;
356 
357 
358     EXCEPTION
359       WHEN OTHERS THEN
360         IF (SQLCODE <> -20001) THEN
361           FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
362           FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
363           FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',
364                     current_calling_sequence);
365           FND_MESSAGE.SET_TOKEN('PARAMETERS',
366               'X_Rowid = '      ||X_Rowid
367           ||', X_INVOICE_NUM = '||X_INVOICE_NUM
368           ||', X_VENDOR_ID = '  ||X_VENDOR_ID
369                                     );
370           FND_MESSAGE.SET_TOKEN('DEBUG_INFO',debug_info);
371         END IF;
372       APP_EXCEPTION.RAISE_EXCEPTION;
373     end CHECK_UNIQUE;
374 
375 /*=============================================================================
376  |  procedure - CHECK_UNIQUE_VOUCHER_NUM
377  |
378  |  DESCRIPTION
379  |      Check if the invoice number within one vendor is unique.
380  |
381  |  KNOWN ISSUES:
382  |
383  |  NOTES
384  |  MODIFICATION HISTORY
385  |  Date         Author             Description of Change
386  |
387  *============================================================================*/
388 
389     PROCEDURE CHECK_UNIQUE_VOUCHER_NUM (
390                   X_ROWID            VARCHAR2,
391                   X_VOUCHER_NUM      VARCHAR2,
392                   X_calling_sequence IN VARCHAR2) IS
393 
394       dummy number := 0;
395       current_calling_sequence    VARCHAR2(2000);
396       debug_info                  VARCHAR2(100);
397 
398     BEGIN
399 
400       current_calling_sequence := 'AP_INVOICES_PKG.CHECK_UNIQUE_VOUCHER_NUM<-'
401                                   || X_calling_sequence;
402 
403       debug_info := 'Count other invoices with same voucher num';
404 
405       select count(1)
406       into   dummy
407       from   ap_invoices
408       where  voucher_num = X_VOUCHER_NUM
409       and    ((X_ROWID is null) or (rowid <> X_ROWID));
410 
411       IF (dummy >= 1) THEN
412         fnd_message.set_name('SQLAP','AP_ALL_DUPLICATE_VALUE');
413         app_exception.raise_exception;
414       END IF;
415 
416     EXCEPTION
417       WHEN OTHERS THEN
418         IF (SQLCODE <> -20001) THEN
419           FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
420           FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
421           FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',
422                                 current_calling_sequence);
423           FND_MESSAGE.SET_TOKEN('PARAMETERS',
424                                 'X_Rowid = '      ||X_Rowid
425                                 ||', X_VOUCHER_NUM = '||X_VOUCHER_NUM);
426           FND_MESSAGE.SET_TOKEN('DEBUG_INFO',debug_info);
427         END IF;
428         APP_EXCEPTION.RAISE_EXCEPTION;
429 
430     END CHECK_UNIQUE_VOUCHER_NUM;
431 
432 /*=============================================================================
433  |  FUNCTION - get_approval_status
434  |
435  |  DESCRIPTION
436  |      returns the invoice approval status lookup code.
437  |
438  |  KNOWN ISSUES:
439  |
440  |  NOTES
441  |      Invoices -'APPROVED'
442  |                'NEEDS REAPPROVAL'
443  |                'NEVER APPROVED'
444  |                 'CANCELLED'
445  |
446  |     Prepayments - 'AVAILABLE'
447  |                   'CANCELLED'
448  |                   'FULL'
449  |                   'UNAPPROVED'
450  |                   'UNPAID'
451  |
452  |  MODIFICATION HISTORY
453  |  Date         Author             Description of Change
454  |
455  *============================================================================*/
456 
457     FUNCTION get_approval_status(
458                  l_invoice_id               IN NUMBER,
459                  l_invoice_amount           IN NUMBER,
460                  l_payment_status_flag      IN VARCHAR2,
461                  l_invoice_type_lookup_code IN VARCHAR2)
462     RETURN VARCHAR2 IS
463 
464       invoice_approval_status       VARCHAR2(25);
465       invoice_approval_flag         VARCHAR2(2);
466       distribution_approval_flag    VARCHAR2(1);
467       encumbrance_flag              VARCHAR2(1);
468       invoice_holds                 NUMBER;
469       cancelled_date                DATE;
470       sum_distributions             NUMBER;
471       dist_var_hold                 NUMBER;
472       match_flag_cnt                NUMBER;
473       l_validated_cnt               NUMBER;
474       l_org_id                      FINANCIALS_SYSTEM_PARAMS_ALL.ORG_ID%TYPE;
475       l_force_revalidation_flag     VARCHAR2(1);
476       --Bugfix: 3854385
477       l_dist_variance		    VARCHAR2(20) := 'DIST VARIANCE';
478       l_line_variance		    VARCHAR2(20) := 'LINE VARIANCE';
479          ---------------------------------------------------------------------
480          -- Declare cursor to establish the invoice-level approval flag
481          --
482          -- The first select simply looks at the match status flag for the
483          -- distributions.  The rest is to cover one specific case when some
484          -- of the distributions are tested (T or A) and some are untested
485          -- (NULL).  The status should be needs reapproval (N).
486          --
487          -- Bug 963755: Modified the approval_cursor below to select the records
488          -- correctly.
489 
490          -- MOAC. Use the tables instead of the SO views in this function
491 
492       -- bug6822570, changed the cursor to fetch
493       -- 'N', in place of NULL, as for match_status_flag
494       -- NULL and 'N' are the same.
495 
496       CURSOR approval_cursor IS
497       SELECT nvl(match_status_flag, 'N')
498       FROM   ap_invoice_distributions_all
499       WHERE  invoice_id = l_invoice_id;
500 
501     BEGIN
502 
503          ---------------------------------------------------------------------
504          -- Get the encumbrance flag
505          -- MOAC.  Included select from ap_invoices_all to get the org_id from
506          --        the invoice_id since it is unique
507 
508 
509       SELECT NVL(fsp.purch_encumbrance_flag,'N'),
510              ai.org_id,
511 	     ai.force_revalidation_flag
512       INTO encumbrance_flag,
513            l_org_id,
514 	   l_force_revalidation_flag
515       FROM ap_invoices_all ai,
516            financials_system_params_all fsp
517       WHERE ai.invoice_id = l_invoice_id
518       AND ai.set_of_books_id = fsp.set_of_books_id
519       AND ai.org_id = fsp.org_id;
520 
521          ---------------------------------------------------------------------
522          -- Get the number of holds for the invoice
523          --
524       SELECT count(*)
525       INTO   invoice_holds
526       FROM   ap_holds_all
527       WHERE  invoice_id = l_invoice_id
528       AND    release_lookup_code is NULL;
529 
530          ---------------------------------------------------------------------
531          -- Bug 787373: Check if DIST VAR hold is placed on this invoice.
532          -- DIST VAR is a special case because it could be placed
533          -- when no distributions exist and in this case, the invoice
534          -- status should be NEEDS REAPPROVAL.
535          --
536       --Bugfix:4539514, added line_variance to the WHERE clause
537       SELECT count(*)
538       INTO   dist_var_hold
539       FROM   ap_holds_all
540       WHERE  invoice_id = l_invoice_id
541       AND    hold_lookup_code IN  (l_dist_variance, l_line_variance)
542       AND    release_lookup_code is NULL;
543 
544          ---------------------------------------------------------------------
545          -- If invoice is cancelled, return 'CANCELLED'.
546          --
547       SELECT ai.cancelled_date
548       INTO   cancelled_date
549       FROM   ap_invoices_all ai
550       WHERE  ai.invoice_id = l_invoice_id;
551 
552       IF (cancelled_date IS NOT NULL) THEN
553         RETURN('CANCELLED');
554       END IF;
555 
556          ---------------------------------------------------------------------
557          -- Bug 963755: Getting the count of distributions with
558          -- match_status_flag not null. We will open the approval_cursor
559          -- only if the count is more than 0.
560          --
561       SELECT count(*)
562       INTO match_flag_cnt
563       FROM ap_invoice_distributions_all aid
564       WHERE aid.invoice_id = l_invoice_id
565       AND aid.match_status_flag IS NOT NULL
566       AND rownum < 2;
567 
568          ---------------------------------------------------------------------
569          -- Establish the invoice-level approval flag
570          --
571          -- Use the following ordering sequence to determine the invoice-level
572          -- approval flag:
573          --                     'N' - Needs Reapproval
574          --                     'T' - Tested
575          --                     'A' - Approved
576          --                     ''  - Never Approved (Old)
577          --                     'NA'  - Never Approved (New per bug 6705321 - epajaril)
578          --                             Handled the status 'NA' in the code (bug6822570)
579          --                     'X' - No Distributions Exist! --666401
580          --
581          -- Initialize invoice-level approval flag
582          --
583       invoice_approval_flag := 'X';
584 
585       IF match_flag_cnt > 0 THEN
586 
587         OPEN approval_cursor;
588 
589         LOOP
590         FETCH approval_cursor INTO distribution_approval_flag;
591         EXIT WHEN approval_cursor%NOTFOUND;
592 
593           -- bug6822570, changed the logic of the Invoice level
594           -- approval status derivation, as there were a few
595           -- cases failing with the previous approach
596 
597           IF (distribution_approval_flag = 'N') THEN
598 
599                -- If the distribution approval_flag encountered
600                -- is 'N' (which is so, when the match_status_flag
601                -- is NULL), we have the following options
602 
603                IF invoice_approval_flag IN ('NA','X') THEN
604 
605                     -- If the current status of the Invoice is
606                     -- no distributions ('X') or Never Validated ('NA')
607                     -- then mark the Invoice as never validated
608 
609                     invoice_approval_flag := 'NA';
610 
611                ELSIF invoice_approval_flag IN ('A','T','N') THEN
612 
613                    -- If the Invoice has been validated at least
614                    -- once, or currently has a needs revalidation
615                    -- status, then make it needs revalidation
616 
617                    invoice_approval_flag := 'N';
618 
619                END IF;
620 
621            ELSIF (distribution_approval_flag = 'T') THEN
622 
623                  -- If then the next distribution encountered is tested
624                  -- then folowing are the options
625 
626                  IF invoice_approval_flag IN ('T','A','X') THEN
627 
628                     -- If currently the Invoice is Approved, or
629                     -- Tested or this is the first distributionn then
630                     -- mark the Invoice as tested
631 
632                    invoice_approval_flag := 'T';
633 
634                 ELSIF invoice_approval_flag IN ('NA','N') THEN
635 
636                    -- If currently the Invoice is Never Approved
637                    -- or at needs revalidation, then the Invoice
638                    -- status should become needs revalidation
639 
640                    invoice_approval_flag := 'N';
641 
642                 END IF;
643 
644            ELSIF (distribution_approval_flag = 'A') THEN
645 
646                  -- If the current distribution is approved,
647                  -- then we have following options
648 
649                  IF invoice_approval_flag IN ('A', 'X') THEN
650 
651                     -- If currently the Invoice is approved or
652                     -- the Invoice has no distributions then
653                     -- Invoice status should become approved
654 
655                     invoice_approval_flag := 'A';
656 
657                  ELSIF invoice_approval_flag = 'T' THEN
658 
659                    -- If the current invoice status is tested
660                    -- it should remain tested
661 
662                    invoice_approval_flag := 'T';
663 
664                  ELSIF invoice_approval_flag IN ('N','NA') THEN
665 
666                    -- If the current invoice status is Needs
667                    -- Reapproval or Never Validated, then the status
668                    -- should become Neeeds Reapproval
669 
670                    invoice_approval_flag := 'N';
671 
672                  END IF;
673 
674           END IF;
675 
676         END LOOP;
677 
678         CLOSE approval_cursor;
679       END IF; -- end of match_flag_cnt
680 
681       --ETAX: Invwkb
682 
683       -- bug6822570, validated that the condition is correct for the present
684       -- logic
685       IF l_force_revalidation_flag = 'Y' THEN
686          IF invoice_approval_flag NOT IN ('X','NA') THEN
687 	    invoice_approval_flag := 'N';
688          ELSE
689             IF match_flag_cnt > 0 THEN
690 
691                SELECT count(*)
692                  INTO l_validated_cnt
693                  FROM ap_invoice_distributions_all aid
694                 WHERE aid.invoice_id = l_invoice_id
695                   AND aid.match_status_flag = 'N'
696                   AND rownum < 2;
697 
698                IF l_validated_cnt > 0 THEN
699                   invoice_approval_flag := 'N';
700                END IF;
701 
702             END IF;
703          END IF;
704       END IF;
705 
706 
707       --Bugfix:4745464, 4923489 (modified the IF condition)
708 
709         -- bug6822570
710         -- Changed the condition since the Invoice Approval
711         -- Flag would never be NULL, and this check is required
712         -- only when the Invoice status is approved, and there
713         -- is no dist var hold
714 
715 	IF ((invoice_approval_flag IN  ('A', 'T')) AND
716             (dist_var_hold = 0)) THEN
717 
718           BEGIN
719 
720            SELECT 'N'
721            INTO invoice_approval_flag
722            FROM ap_invoice_lines_all ail
723            WHERE ail.invoice_id = l_invoice_id
724            AND ail.amount <>
725              ( SELECT NVL(SUM(NVL(aid.amount,0)),0)
726       	       FROM ap_invoice_distributions_all aid
727 	       WHERE aid.invoice_id = ail.invoice_id
728 	       AND   aid.invoice_line_number = ail.line_number
729 	       --bugfix:4959567
730                AND   ( aid.line_type_lookup_code <> 'RETAINAGE'
731                         OR (ail.line_type_lookup_code = 'RETAINAGE RELEASE' AND
732                             aid.line_type_lookup_code = 'RETAINAGE') )
733                /*
734 	       AND   (ail.line_type_lookup_code <> 'ITEM'
735 	              OR (aid.line_type_lookup_code <> 'PREPAY'
736 	                  and aid.prepay_tax_parent_id IS  NULL)
737                      )
738                */
739 	       AND   (AIL.line_type_lookup_code NOT IN ('ITEM', 'RETAINAGE RELEASE')
740                       OR (AIL.line_type_lookup_code IN ('ITEM', 'RETAINAGE RELEASE')
741                           AND (AID.prepay_distribution_id IS NULL
742                                OR (AID.prepay_distribution_id IS NOT NULL
743                                    AND AID.line_type_lookup_code NOT IN ('PREPAY', 'REC_TAX', 'NONREC_TAX')))))
744 	       );
745 
746            EXCEPTION WHEN OTHERS THEN
747               NULL;
748            END;
749 
750          END IF;
751 
752         -- bug6047348
753         -- Changed this condition also same as the above
754 
755         IF ((invoice_approval_flag in ('A', 'T')) AND
756             (dist_var_hold = 0))  THEN
757 
758           BEGIN
759 
760 	   SELECT 'N'
761            INTO   invoice_approval_flag
762            FROM   ap_invoice_lines_all AIL, ap_invoices_all A
763            WHERE  AIL.invoice_id = A.invoice_id
764            AND    AIL.invoice_id = l_invoice_id
765            AND    ((AIL.line_type_lookup_code <> 'TAX'
766                    and (AIL.line_type_lookup_code NOT IN ('AWT','PREPAY')
767                         or NVL(AIL.invoice_includes_prepay_flag,'N') = 'Y') OR
768                   (AIL.line_type_lookup_code = 'TAX'
769                   /* bug 5222316 */
770                    and (AIL.prepay_invoice_id IS NULL
771                         or (AIL.prepay_invoice_id is not null
772                             and NVL(AIL.invoice_includes_prepay_flag, 'N') = 'Y')))))
773                --    and AIL.prepay_invoice_id IS NULL)))
774            GROUP BY A.invoice_id, A.invoice_amount, A.net_of_retainage_flag
775            HAVING A.invoice_amount <>
776                   nvl(SUM(nvl(AIL.amount,0) + decode(A.net_of_retainage_flag,
777                                  'Y', nvl(AIL.retained_amount,0),0)),0);
778 
779            EXCEPTION WHEN OTHERS THEN
780               NULL;
781            END;
782 
783          END IF;
784 
785 
786          ---------------------------------------------------------------------
787          -- Bug 719322: Bug 719322 was created by the fix to bug 594189. Re-fix
788          -- for bug 594189 would fix bug 719322.
789 
790          -- Re-fix for bug 594189
791          -- With encumbrance on, if after an invoice has been approved, the
792          -- user changes the invoice amount, then the invoice amount would
793          -- no longer match the sum of the distribution amounts. In this case,
794          -- the status should go to 'NEEDS REAPPROVAL'.
795 
796          -- eTax Uptake.  Use of prepay_distribution_id to determine
797          -- if the REC_TAX and NONREC_TAX distribution are related
798          -- to the prepayment application and should be included in the
799          -- total of the distributions if the invoice_includes_prepay_flag is
800          -- Y.  Included ap_invoice_lines_all in select since the flag
801          -- at the dist level is obsolete.
802 
803       IF (encumbrance_flag = 'Y') AND (invoice_approval_flag = 'A') THEN
804 
805          SELECT NVL(SUM(nvl(aid.amount,0)), 0)
806            INTO sum_distributions
807            FROM ap_invoice_distributions_all aid,
808                 ap_invoice_lines_all ail
809           WHERE ail.invoice_id = l_invoice_id
810             AND aid.invoice_id = ail.invoice_id
811             AND aid.invoice_line_number = ail.line_number
812             AND (aid.line_type_lookup_code <> 'RETAINAGE'
813                  OR (ail.line_type_lookup_code = 'RETAINAGE RELEASE'
814                      and aid.line_type_lookup_code = 'RETAINAGE') )
815             AND ((aid.line_type_lookup_code NOT IN ('AWT','PREPAY')
816                   AND aid.prepay_distribution_id IS NULL)
817                 OR NVL(ail.invoice_includes_prepay_flag,'N') = 'Y');
818 
819         IF (l_invoice_amount <> sum_distributions) THEN
820           invoice_approval_flag := 'N';
821         END IF;
822       END IF;  -- end of check encumbrance_flag
823 
824          ---------------------------------------------------------------------
825          -- Derive the translated approval status from the approval flag
826          --
827       IF (encumbrance_flag = 'Y') THEN
828 
829         IF (invoice_approval_flag = 'A' AND invoice_holds = 0) THEN
830           invoice_approval_status := 'APPROVED';
831         ELSIF ((invoice_approval_flag in ('A') AND invoice_holds > 0)
832                OR (invoice_approval_flag IN ('T','N'))) THEN
833           invoice_approval_status := 'NEEDS REAPPROVAL';
834         ELSIF (dist_var_hold >= 1) THEN
835                  --It's assumed here that the user won't place this hold
836                  --manually before approving.  If he does, status will be
837                  --NEEDS REAPPROVAL.  dist_var_hold can result when there
838                  --are no distributions or there are but amounts don't
839                  --match.  It can also happen when an invoice is created with
840                  --no distributions, then approve the invoice, then create the
841                  --distribution.  So, in this case, although the match flag
842                  --is null, we still want to see the status as NEEDS REAPPR.
843           invoice_approval_status := 'NEEDS REAPPROVAL';
844         -- bug6822570, removed the condition for the Invoice Approval flag
845         -- being NULL, and added the condition for 'NA'
846         ELSIF (invoice_approval_flag IN ('X','NA') AND dist_var_hold = 0) THEN
847             invoice_approval_status := 'NEVER APPROVED';
848         END IF;
849 
850       ELSIF (encumbrance_flag = 'N') THEN
851         IF (invoice_approval_flag IN ('A','T') AND invoice_holds = 0) THEN
852           invoice_approval_status := 'APPROVED';
853         ELSIF ((invoice_approval_flag IN ('A','T') AND invoice_holds > 0) OR
854                (invoice_approval_flag = 'N')) THEN
855           invoice_approval_status := 'NEEDS REAPPROVAL';
856         ELSIF (dist_var_hold >= 1) THEN
857           invoice_approval_status := 'NEEDS REAPPROVAL';
858         -- bug6822570, removed the condition for the invoice approval flag
859         -- being NULL, and added the condition for 'NA'
860         ELSIF (invoice_approval_flag IN ('X','NA') AND dist_var_hold = 0) THEN
861                  -- Bug 787373: A NULL flag indicate that APPROVAL has not
862                  -- been run for this invoice, therefore, even if manual
863                  -- holds exist, status should be NEVER APPROVED.
864           invoice_approval_status := 'NEVER APPROVED';
865         END IF;
866       END IF;
867 
868          ---------------------------------------------------------------------
869          -- If this a prepayment, find the appropriate prepayment status
870          --
871       if (l_invoice_type_lookup_code = 'PREPAYMENT') then
872         if (invoice_approval_status = 'APPROVED') then
873           if (NVL(l_payment_status_flag , 'N') <> 'Y') then --bug6598052
874             invoice_approval_status := 'UNPAID';
875           else
876             -- This prepayment is paid
877             if (AP_INVOICES_UTILITY_PKG.get_prepay_amount_remaining(l_invoice_id) = 0) then
878               invoice_approval_status := 'FULL';
879             elsif (AP_INVOICES_UTILITY_PKG.get_prepayment_type(l_invoice_id) = 'PERMANENT') THEN
880               invoice_approval_status := 'PERMANENT';
881             else
882               invoice_approval_status := 'AVAILABLE';
883             end if; -- end of check AP_INVOICES_UTILITY_PKG call
884           end if; -- end of check l_payment_status_flag
885         elsif (invoice_approval_status = 'NEVER APPROVED') then
886              -- This prepayment in unapproved
887           invoice_approval_status := 'UNAPPROVED';
888         end if; -- end of invoice_approval_status
889       end if; -- end of l_invoice_type_lookup_code
890 
891       RETURN(invoice_approval_status);
892     END get_approval_status;
893 
894 
895 /*===========================================================================
896  |  FUNCTION - get_po_number
897  |
898  |  DESCRIPTION
899  |      returns the PO number matched to invoice, or
900  |      with. the 'UNMATCHED' lookup code if not matched, or the
901  |      'ANY MULTIPLE'lookup code if matched to multiple POs.
902  |      Because of Lines project, price correction, quantity correction should
903  |      be taken into account on top op base match. The logic is based on the
904  |      following assumptions:
905  |        1. po_header_id and po_line_location_id are populated for both
906  |           receipt matching and po matching
907  |        2. it does not take CHARGES_TO_RECEIPT match type into account.
908  |
909  |  KNOWN ISSUES:
910  |
911  |  NOTES:
912  |      Bug# 450052: Added GROUP BY and HAVING clauses to make sure that
913  |      if all distributions matched to a PO have been reversed, it is not
914  |      considered matched
915  |
916  |  MODIFICATION HISTORY
917  |  Date         Author             Description of Change
918  |
919  *==========================================================================*/
920 
921     FUNCTION get_po_number(l_invoice_id IN NUMBER)
922     RETURN VARCHAR2 IS
923       po_number VARCHAR2(25) := 'UNMATCHED';
924       l_line_matched_amount  NUMBER;
925       l_po_header_id NUMBER;
926       l_corrected_amount NUMBER;
927      /* Bug 4669905. Modified the Cursor */
928       CURSOR po_number_cursor IS
929       SELECT DISTINCT ph.segment1, ph.po_header_id,
930              NVL(SUM(L.amount),0)
931       FROM   ap_invoice_lines_all L,
932              po_headers PH
933       WHERE  L.invoice_id = l_invoice_id
934       AND    L.po_header_id = PH.po_header_id
935       AND    L.match_type IN ( 'PRICE_CORRECTION', 'QTY_CORRECTION',
936                                'ITEM_TO_PO', 'ITEM_TO_RECEIPT', 'AMOUNT_CORRECTION',
937                                'RETRO PRICE ADJUSTMENT','ITEM_TO_SERVICE_PO')  --Bug6931134
938       AND    NVL (L.discarded_flag, 'N' ) <> 'Y'
939       AND    NVL (L.cancelled_flag, 'N' ) <> 'Y'
940       GROUP BY PH.po_header_id, PH.segment1
941       HAVING ( NVL(SUM(L.amount), 0) <> 0 OR
942                NVL(SUM(L.quantity_invoiced), 0) <> 0);
943 
944     BEGIN
945 
946       OPEN po_number_cursor;
947       LOOP
948       FETCH po_number_cursor
949       INTO  po_number, l_po_header_id,
950             l_line_matched_amount;
951       EXIT WHEN po_number_cursor%NOTFOUND;
952 
953         IF (po_number_cursor%ROWCOUNT > 1) THEN
954           po_number := 'ANY MULTIPLE';
955           EXIT;
956         ELSE  /* Bug 4669905 */
957           SELECT NVL(SUM(AIL.amount), 0)
958           INTO   l_corrected_amount
959           FROM   ap_invoice_lines_all AIL
960           WHERE  corrected_inv_id = l_invoice_id
961           AND    po_header_id = l_po_header_id
962           AND    NVL( AIL.discarded_flag, 'N' ) <> 'Y'
963           AND    NVL( AIL.cancelled_flag, 'N' ) <> 'Y' ;
964 
965           IF ((-1)*l_corrected_amount >= l_line_matched_amount) THEN
966             po_number := 'UNMATCHED';
967           END IF;
968         END IF;
969       END LOOP;
970       CLOSE po_number_cursor;
971 
972       RETURN(po_number);
973 
974     END get_po_number;
975 
976 /*=============================================================================
977  |  FUNCTION - get_release_number
978  |
979  |  DESCRIPTION
980  |      returns the release number matched to invoice  for a BLANKET PO, or
981  |      the 'UNMATCHED' lookup code if not matched or matched to a combination
982  |      of BLANKET/NON-BLANKET POs, or the 'ANY MULTIPLE' lookup code if
983  |      matched to multiple POs (all of which must be BLANKET).
984  |
985  |  KNOWN ISSUES:
986  |
987  |  NOTES:
988  |
989  |  MODIFICATION HISTORY
990  |  Date         Author             Description of Change
991  |
992  *============================================================================*/
993 
994     FUNCTION get_release_number(l_invoice_id IN NUMBER)
995     RETURN VARCHAR2 IS
996       po_release_number VARCHAR2(25) := 'UNMATCHED';
997       l_shipment_type   po_line_locations.shipment_type%TYPE;
998 
999       CURSOR po_shipment_type_cursor IS
1000       SELECT DISTINCT(pll.shipment_type)
1001       FROM   ap_invoice_lines L,
1002              po_line_locations PLL
1003       WHERE  L.invoice_id = l_invoice_id
1004       AND   NOT EXISTS (SELECT  AIL.corrected_inv_id
1005                           FROM  ap_invoice_lines AIL
1006                          WHERE NVL( AIL.discarded_flag, 'N' ) <> 'Y'
1007                            AND NVL( AIL.cancelled_flag, 'N' ) <> 'Y'
1008                            AND  AIL.corrected_inv_id =  L.invoice_id)
1009       AND    L.po_line_location_id = PLL.line_location_id
1010       AND    L.match_type IN ( 'PRICE_CORRECTION', 'QTY_CORRECTION',
1011                                'ITEM_TO_PO', 'ITEM_TO_RECEIPT',
1012                                'RETRO PRICE ADJUSTMENT')
1013 /*
1014 5000309 fbreslin: exclude line if discared or cancled
1015 */
1016       AND    NVL (L.discarded_flag, 'N' ) <> 'Y'
1017       AND    NVL (L.cancelled_flag, 'N' ) <> 'Y'
1018       GROUP BY PLL.shipment_type
1019       HAVING ( NVL(SUM(L.amount), 0) <> 0 OR
1020                NVL(SUM(L.quantity_invoiced), 0) <> 0);
1021 
1022 
1023       CURSOR po_release_number_cursor IS
1024       SELECT DISTINCT(PRL.release_num)
1025       FROM ap_invoice_lines L,
1026            po_line_locations PLL,
1027            po_releases PRL
1028       WHERE  L.invoice_id = l_invoice_id
1029       AND NOT EXISTS (SELECT  AIL.corrected_inv_id
1030                           FROM  ap_invoice_lines AIL
1031                          WHERE NVL( AIL.discarded_flag, 'N' ) <> 'Y'
1032                            AND NVL( AIL.cancelled_flag, 'N' ) <> 'Y'
1033                            AND  AIL.corrected_inv_id =  L.invoice_id)
1034       AND    L.po_line_location_id = PLL.line_location_id
1035       AND    L.match_type IN ( 'PRICE_CORRECTION', 'QTY_CORRECTION',
1036                                'ITEM_TO_PO', 'ITEM_TO_RECEIPT',
1037                                 'RETRO PRICE ADJUSTMENT')
1038 /*
1039 5000309 fbreslin: exclude line if discared or cancled
1040 */
1041       AND    NVL (L.discarded_flag, 'N' ) <> 'Y'
1042       AND    NVL (L.cancelled_flag, 'N' ) <> 'Y'
1043       AND   PRL.po_release_id = PLL.po_release_id
1044       GROUP BY PRL.release_num
1045       HAVING ( NVL(SUM(L.amount), 0) <> 0 OR
1046                NVL(SUM(L.quantity_invoiced), 0) <> 0);
1047 
1048     BEGIN
1049 
1050       OPEN po_shipment_type_cursor;
1051       LOOP
1052       FETCH po_shipment_type_cursor INTO l_shipment_type;
1053       EXIT WHEN po_shipment_type_cursor%NOTFOUND;
1054 
1055         IF (po_shipment_type_cursor%ROWCOUNT > 1) THEN
1056           po_release_number := NULL;
1057           EXIT;
1058         END IF;
1059       END LOOP;
1060       CLOSE po_shipment_type_cursor;
1061 
1062       if (po_release_number is not NULL) then
1063         OPEN po_release_number_cursor;
1064         LOOP
1065         FETCH po_release_number_cursor INTO po_release_number;
1066         EXIT WHEN po_release_number_cursor%NOTFOUND;
1067           IF (po_release_number_cursor%ROWCOUNT > 1) THEN
1068             po_release_number := 'ANY MULTIPLE';
1069             EXIT;
1070           END IF;
1071         END LOOP;
1072         CLOSE po_release_number_cursor;
1073       else
1074         po_release_number := 'UNMATCHED';
1075       end if;
1076 
1077       RETURN(po_release_number);
1078 
1079     END get_release_number;
1080 
1081 /*=============================================================================
1082  |  FUNCTION - get_receipt_number
1083  |
1084  |  DESCRIPTION
1085  |      returns the receipt number matched to invoice, or the 'UNMATCHED'
1086  |      lookup code if not matched, or the 'ANY MULTIPLE' lookup code if
1087  |      matched to multiple receipts.
1088  |
1089  |  KNOWN ISSUES:
1090  |
1091  |  NOTES:
1092  |
1093  |  MODIFICATION HISTORY
1094  |  Date         Author             Description of Change
1095  |
1096  *============================================================================*/
1097 
1098     FUNCTION get_receipt_number(l_invoice_id IN NUMBER)
1099     RETURN VARCHAR2 IS
1100       receipt_number VARCHAR2(25) := 'UNMATCHED';
1101 
1102       CURSOR receipt_number_cursor IS
1103       SELECT DISTINCT(rsh.receipt_num)
1104       FROM   ap_invoice_lines L,
1105              rcv_transactions RTXN,
1106              rcv_shipment_headers RSH
1107       WHERE  L.invoice_id = l_invoice_id
1108       AND NOT EXISTS (SELECT  AIL.corrected_inv_id
1109                           FROM  ap_invoice_lines AIL
1110                          WHERE NVL( AIL.discarded_flag, 'N' ) <> 'Y'
1111                            AND NVL( AIL.cancelled_flag, 'N' ) <> 'Y'
1112                            AND  AIL.corrected_inv_id =  L.invoice_id)
1113       AND    L.rcv_transaction_id = RTXN.transaction_id
1114       AND    RSH.shipment_header_id = RTXN.shipment_header_id
1115       AND    L.match_type IN ( 'PRICE_CORRECTION', 'QTY_CORRECTION',
1116                                'ITEM_TO_RECEIPT',
1117                                'RETRO PRICE ADJUSTMENT')
1118 /*
1119 5000309 fbreslin: exclude line if discared or cancled
1120 */
1121       AND    NVL (L.discarded_flag, 'N' ) <> 'Y'
1122       AND    NVL (L.cancelled_flag, 'N' ) <> 'Y'
1123       GROUP BY rsh.shipment_header_id, rsh.receipt_num
1124       HAVING ( NVL(SUM(L.amount), 0) <> 0 OR
1125                NVL(SUM(L.quantity_invoiced), 0) <> 0);
1126 
1127     BEGIN
1128 
1129       OPEN receipt_number_cursor;
1130       LOOP
1131       FETCH receipt_number_cursor INTO receipt_number;
1132       EXIT WHEN receipt_number_cursor%NOTFOUND;
1133 
1134         IF (receipt_number_cursor%ROWCOUNT > 1) THEN
1135           receipt_number := 'ANY MULTIPLE';
1136           EXIT;
1137         END IF;
1138 
1139       END LOOP;
1140       CLOSE receipt_number_cursor;
1141 
1142       RETURN(receipt_number);
1143     END get_receipt_number;
1144 
1145 /*=============================================================================
1146  |  FUNCTION -  get_po_number_list
1147  |
1148  |  DESCRIPTION
1149  |      returns all the PO Numbers matched to this invoice (comma delimited)
1150  |      or NULL if not matched.
1151  |
1152  |  KNOWN ISSUES:
1153  |
1154  |  NOTES:
1155  |      Bug# 450052: Added GROUP BY and HAVING clauses to make sure that
1156  |      if all distributions matched to a PO have been reversed, it is not
1157  |      considered matched
1158  |
1159  |  MODIFICATION HISTORY
1160  |  Date         Author             Description of Change
1161  |
1162  *============================================================================*/
1163 
1164     FUNCTION get_po_number_list(l_invoice_id IN NUMBER)
1165     RETURN VARCHAR2 IS
1166       po_number      VARCHAR2(20);
1167       po_number_list VARCHAR2(2000) := NULL;
1168 
1169      CURSOR po_number_cursor IS
1170       SELECT DISTINCT(ph.segment1)
1171       FROM   ap_invoice_lines L,
1172              po_headers PH
1173       WHERE  L.invoice_id = l_invoice_id
1174       AND   NOT EXISTS (SELECT  AIL.corrected_inv_id
1175                           FROM  ap_invoice_lines AIL
1176                          WHERE NVL( AIL.discarded_flag, 'N' ) <> 'Y'
1177                            AND NVL( AIL.cancelled_flag, 'N' ) <> 'Y'
1178                            AND  AIL.corrected_inv_id =  L.invoice_id)
1179       AND    L.po_header_id = PH.po_header_id
1180       AND    L.match_type IN ( 'PRICE_CORRECTION', 'QTY_CORRECTION',
1181                                'ITEM_TO_PO', 'ITEM_TO_RECEIPT',
1182                                'RETRO PRICE ADJUSTMENT')
1183 /*
1184 5000309 fbreslin: exclude line if discared or cancled
1185 */
1186       AND    NVL (L.discarded_flag, 'N' ) <> 'Y'
1187       AND    NVL (L.cancelled_flag, 'N' ) <> 'Y'
1188       GROUP BY PH.po_header_id, PH.segment1
1189       HAVING ( NVL(SUM(L.amount), 0) <> 0 OR
1190                NVL(SUM(L.quantity_invoiced), 0) <> 0);
1191 
1192     BEGIN
1193 
1194       OPEN po_number_cursor;
1195       LOOP
1196       FETCH po_number_cursor INTO po_number;
1197       EXIT WHEN po_number_cursor%NOTFOUND;
1198         IF (po_number_list IS NOT NULL) THEN
1199           po_number_list := po_number_list || ', ';
1200         END IF;
1201         po_number_list := po_number_list || po_number;
1202 
1203       END LOOP;
1204       CLOSE po_number_cursor;
1205 
1206       RETURN(po_number_list);
1207 
1208     END get_po_number_list;
1209 
1210 /*=============================================================================
1211  |  FUNCTION -  get_amount_withheld
1212  |
1213  |  DESCRIPTION
1214  |      returns the AWT withheld amount on an invoice.
1215  |
1216  |  KNOWN ISSUES:
1217  |
1218  |  NOTES:
1219  |
1220  |  MODIFICATION HISTORY
1221  |  Date         Author             Description of Change
1222  |
1223  *============================================================================*/
1224 
1225     FUNCTION get_amount_withheld(l_invoice_id IN NUMBER)
1226     RETURN NUMBER IS
1227       amount_withheld           NUMBER := 0;
1228     BEGIN
1229 
1230       select (0 - sum(nvl(amount,0)))
1231       into   amount_withheld
1232       from   ap_invoice_distributions
1233       where  invoice_id = l_invoice_id
1234       and    line_type_lookup_code = 'AWT';
1235 
1236       return(amount_withheld);
1237 
1238     END get_amount_withheld;
1239 
1240 /*=============================================================================
1241  |  FUNCTION -  get_prepaid_amount
1242  |
1243  |  DESCRIPTION
1244  |      rreturns the prepayment amount on on an invoice.
1245  |
1246  |  KNOWN ISSUES:
1247  |
1248  |  NOTES:
1249  |
1250  |  MODIFICATION HISTORY
1251  |  Date         Author             Description of Change
1252  |
1253  *============================================================================*/
1254 
1255     FUNCTION get_prepaid_amount(l_invoice_id IN NUMBER)
1256     RETURN NUMBER IS
1257       l_prepaid_amount           NUMBER := 0;
1258     BEGIN
1259       -- eTax Uptake.  This function maybe obsolete in the future, but for
1260       -- now it should be consistent.  Use the ap_prepay_utils_pkg API.
1261 
1262       l_prepaid_amount := ap_prepay_utils_pkg.get_prepaid_amount(l_invoice_id);
1263 
1264      return(l_prepaid_amount);
1265 
1266     END get_prepaid_amount;
1267 
1268 
1269 /*=============================================================================
1270  |  FUNCTION -  get_notes_count
1271  |
1272  |  DESCRIPTION
1273  |      returns the number of notes associated with an invoice
1274  |
1275  |  KNOWN ISSUES:
1276  |
1277  |  NOTES:
1278  |
1279  |  MODIFICATION HISTORY
1280  |  Date         Author             Description of Change
1281  |
1282  *============================================================================*/
1283 
1284     FUNCTION get_notes_count(l_invoice_id IN NUMBER)
1285     RETURN NUMBER IS
1286       notes_count           NUMBER := 0;
1287     BEGIN
1288 
1289       SELECT COUNT(*)
1290       INTO   notes_count
1291       FROM   po_note_references
1292       WHERE  table_name = 'AP_INVOICES'
1293       AND    foreign_id = l_invoice_id;
1294 
1295       return(notes_count);
1296 
1297     END get_notes_count;
1298 
1299 /*=============================================================================
1300  |  FUNCTION -  get_holds_count
1301  |
1302  |  DESCRIPTION
1303  |      returns the number of unreleased holds placed on an invoice.
1304  |
1305  |  KNOWN ISSUES:
1306  |
1307  |  NOTES:
1308  |
1309  |  MODIFICATION HISTORY
1310  |  Date         Author             Description of Change
1311  |
1312  *============================================================================*/
1313 
1314     FUNCTION get_holds_count(l_invoice_id IN NUMBER)
1315     RETURN NUMBER
1316     IS
1317       holds_count           NUMBER := 0;
1318     BEGIN
1319 
1320       SELECT COUNT(*)
1321       INTO   holds_count
1322       FROM   ap_holds
1323       WHERE  release_lookup_code is null
1324       AND    invoice_id = l_invoice_id;
1325 
1326       RETURN (holds_count);
1327 
1328     END get_holds_count;
1329 
1330 /*=============================================================================
1331  |  FUNCTION -  get_sched_holds_count
1332  |
1333  |  DESCRIPTION
1334  |      returns the number of unreleased holds placed on an payment schedules.
1335  |
1336  |  KNOWN ISSUES:
1337  |
1338  |  NOTES:
1339  |
1340  |  MODIFICATION HISTORY
1341  |  Date         Author             Description of Change
1342  |
1343  *============================================================================*/
1344 
1345     FUNCTION get_sched_holds_count(l_invoice_id IN NUMBER)
1346     RETURN NUMBER
1347     IS
1348       holds_count           NUMBER := 0;
1349     BEGIN
1350 
1351       SELECT COUNT(*)
1352       INTO   holds_count
1353       FROM   ap_payment_schedules_all
1354       WHERE  hold_flag = 'Y'
1355       AND    invoice_id = l_invoice_id;
1356 
1357       RETURN (holds_count);
1358 
1359     END get_sched_holds_count;
1360 
1361 /*=============================================================================
1362  |  FUNCTION -  get_total_prepays
1363  |
1364  |  DESCRIPTION
1365  |      returns the total number of prepayments that exist for a vendor
1366  |      (not fully applied, not permanent).We've declared a server-side
1367  |      function that can be accessed from our invoices view so as to improve
1368  |      performance when retrieving invoices in the Invoice Gateway.
1369  |
1370  |  KNOWN ISSUES:
1371  |
1372  |  NOTES:
1373  |
1374  |  MODIFICATION HISTORY
1375  |  Date         Author             Description of Change
1376  |
1377  *============================================================================*/
1378 
1379     FUNCTION get_total_prepays(
1380                  l_vendor_id    IN NUMBER,
1381                  l_org_id       IN NUMBER)
1382     RETURN NUMBER
1383     IS
1384       prepay_count           NUMBER := 0;
1385     BEGIN
1386 
1387       SELECT  COUNT(*)
1388       INTO   prepay_count
1389       FROM   ap_invoices ai
1390       WHERE  vendor_id = l_vendor_id
1391       AND    (( l_org_id IS NOT NULL AND
1392                 ai.org_id = l_org_id)
1393              OR l_org_id IS NULL)
1394       AND    invoice_type_lookup_code = 'PREPAYMENT'
1395       AND    earliest_settlement_date IS NOT NULL
1396       AND    AP_INVOICES_UTILITY_PKG.get_prepay_amount_remaining(ai.invoice_id) > 0;
1397 
1398          RETURN(prepay_count);
1399 
1400      END get_total_prepays;
1401 
1402 /*=============================================================================
1403  |  FUNCTION -  get_available_prepays
1404  |
1405  |  DESCRIPTION
1406  |      returns the number of available prepayments to a vendor which can be
1407  |      applied. We've declared a server-side function that can be accessed
1408  |      from our invoices view so as to improve performance when retrieving
1409  |      invoices in the Invoice Gateway.
1410  |
1411  |  KNOWN ISSUES:
1412  |
1413  |  NOTES:
1414  |
1415  |  MODIFICATION HISTORY
1416  |  Date         Author             Description of Change
1417  | 09-JAN-06     KGURUMUR           Made changes for improving performance
1418  *============================================================================*/
1419 
1420     FUNCTION get_available_prepays(
1421                  l_vendor_id    IN NUMBER,
1422                  l_org_id       IN NUMBER)
1423     RETURN NUMBER
1424     IS
1425       prepay_count           NUMBER := 0;
1426       l_prepay_amount_remaining NUMBER:=0;
1427          /*Bug4579216
1428            Replaced the existing logic with a cursor defined for the same
1429            which just selects the prepayment invoices for the vendor.This
1430            is done for performance overheads.The comparison of earliest
1431            settlement date would be done with the cursor variable,also the
1432            earlier select statement which would call the get_total_prepays
1433            as a filter is removed and logic is implemented here as this                    would reduce the wait time*/
1434          CURSOR prepayment_invoices IS
1435          SELECT earliest_settlement_date,invoice_id
1436          from
1437          ap_invoices
1438          where vendor_id=l_vendor_id
1439          and invoice_type_lookup_code='PREPAYMENT'
1440          /*7015402*/
1441          and payment_status_flag = 'Y'
1442          and earliest_settlement_date is not null
1443          AND    (( l_org_id IS NOT NULL AND
1444                    org_id = l_org_id)
1445                    OR l_org_id IS NULL);
1446 
1447      BEGIN
1448          /*Bug 4579216*/
1449          for i in prepayment_invoices
1450          loop
1451           if(i.earliest_settlement_date<=(sysdate)) then
1452              l_prepay_amount_remaining:=0;
1453              l_prepay_amount_remaining:=
1454              AP_INVOICES_UTILITY_PKG.get_prepay_amount_remaining(i.invoice_id);
1455              if(l_prepay_amount_remaining>0) then
1456                     prepay_count:=prepay_count+1;
1457              end if;
1458           end if;
1459          end loop;
1460          return(prepay_count);
1461 
1462 END get_available_prepays;
1463 
1464 /*=============================================================================
1465  |  FUNCTION - get_encumbered_flag()
1466  |
1467  |  DESCRIPTION
1468  |      returns the invoice-level encumbrance status of an invoice.
1469  |
1470  |  KNOWN ISSUES:
1471  |
1472  |  NOTES:
1473  | ---------------------------------------------------------------------
1474  |      -- Establish the invoice-level encumbrance flag.
1475  |      -- Function will return one of the following statuses
1476  |      --
1477  |      --                     'Y' - Fully encumbered
1478  |      --                     'P' - One or more distributions is
1479  |      --                           encumbered, but not all
1480  |      --                     'N' - No distributions are encumbered
1481  |      --                     ''  - Budgetary control disabled
1482  |      --
1483  |  ---------------------------------------------------------------------
1484  |      -- Meaning of distribution encumbrance_flag:
1485  |      -- Y: Regular line, has already been successfully encumbered by AP.
1486  |      -- W: Regular line, has been encumbered in advisory mode even though
1487  |      --    insufficient funds existed.
1488  |      -- H: Line has not been encumbered yet, since it was put on hold.
1489  |      -- N or Null : Line not yet seen by this code.
1490  |      -- D: Same as Y for reversal distribution line.
1491  |      -- X: Same as W for reversal distribution line.
1492  |      -- P: Same as H for reversal distribution line.
1493  |      -- R: Same as N for reversal distribution line.
1494  |
1495  |  MODIFICATION HISTORY
1496  |  Date         Author             Description of Change
1497  |
1498  *============================================================================*/
1499 
1500     FUNCTION get_encumbered_flag(l_invoice_id IN NUMBER)
1501     RETURN VARCHAR2
1502     IS
1503       l_purch_encumbrance_flag    VARCHAR2(1) := '';
1504       l_encumbered_flag           VARCHAR2(1) := '';
1505       l_distribution_count        number      := 0;
1506       l_encumbered_count          number      := 0;
1507       l_org_id                    FINANCIALS_SYSTEM_PARAMS_ALL.ORG_ID%TYPE;
1508 
1509       CURSOR encumbrance_flag_cursor is
1510       SELECT nvl(encumbered_flag,'N')
1511       FROM   ap_invoice_distributions
1512       WHERE  invoice_id = l_invoice_id;
1513 
1514       /*7388641 - Checking encumbrance for invoice having just self
1515         assessed tax distributions, not a normal distributions and
1516 	encumbrance is enabled */
1517 
1518       CURSOR encumb_flag_in_self_tax_cursor is
1519       SELECT nvl(encumbered_flag,'N')
1520       FROM   ap_self_assessed_tax_dist
1521       WHERE  invoice_id = l_invoice_id;
1522 
1523     BEGIN
1524 
1525       SELECT NVL(fsp.purch_encumbrance_flag,'N'), ai.org_id
1526         INTO l_purch_encumbrance_flag, l_org_id
1527         FROM ap_invoices_all ai,
1528              financials_system_params_all fsp
1529        WHERE ai.invoice_id = l_invoice_id
1530          AND ai.org_id = fsp.org_id;
1531 
1532       IF (l_purch_encumbrance_flag = 'N') THEN
1533         RETURN('');
1534       END IF;
1535 
1536       OPEN encumbrance_flag_cursor;
1537       LOOP
1538       FETCH encumbrance_flag_cursor INTO l_encumbered_flag;
1539       EXIT WHEN encumbrance_flag_cursor%NOTFOUND;
1540         IF (l_encumbered_flag in ('Y','D','W','X')) THEN
1541           l_encumbered_count := l_encumbered_count + 1;
1542         END IF;
1543           l_distribution_count := l_distribution_count + 1;
1544       END LOOP;
1545 
1546       /*7388641   Taking the count of encumbrance distributions
1547         if self assed tax distributions exists for invoice */
1548       OPEN encumb_flag_in_self_tax_cursor;
1549       LOOP
1550          FETCH encumb_flag_in_self_tax_cursor INTO l_encumbered_flag;
1551          EXIT WHEN encumb_flag_in_self_tax_cursor%NOTFOUND;
1552             IF (l_encumbered_flag in ('Y','D','W','X')) THEN
1553               l_encumbered_count := l_encumbered_count + 1;
1554             END IF;
1555             l_distribution_count := l_distribution_count + 1;
1556       END LOOP;
1557 
1558       --End of 7388641
1559 
1560       IF (l_encumbered_count > 0) THEN
1561         -- At least one distribution is encumbered
1562         IF (l_distribution_count = l_encumbered_count) THEN
1563           -- Invoice is fully encumbered
1564           RETURN('Y');
1565         ELSE
1566           -- Invoice is partially encumbered
1567           RETURN('P');
1568         END IF;
1569       ELSE
1570         -- No distributions are encumbered
1571         RETURN('N');
1572       END IF;
1573 
1574      END get_encumbered_flag;
1575 
1576 /*=============================================================================
1577  |  FUNCTION - get_amount_hold_flag
1578  |
1579  |  DESCRIPTION
1580  |      returns a flag designating whether an invoice has unreleased amounts
1581  |      holds We've declared a server-side function that can be accessed from
1582  |      our invoices view so as to improve performance when retrieving invoices
1583  |      in the Invoice Gateway.
1584  |
1585  |  KNOWN ISSUES:
1586  |
1587  |  NOTES:
1588  |
1589  |  MODIFICATION HISTORY
1590  |  Date         Author             Description of Change
1591  |
1592  *============================================================================*/
1593 
1594     FUNCTION get_amount_hold_flag(l_invoice_id IN NUMBER)
1595     RETURN VARCHAR2
1596     IS
1597       l_amount_hold_flag  VARCHAR2(1) := 'N';
1598       --Bugfix:3854385
1599       l_amount	VARCHAR2(10) := 'AMOUNT';
1600 
1601       cursor amount_hold_flag_cursor is
1602       SELECT 'Y'
1603         FROM ap_holds
1604        WHERE invoice_id = l_invoice_id
1605          AND hold_lookup_code = l_amount
1606          AND release_lookup_code IS NULL;
1607 
1608     BEGIN
1609 
1610       OPEN amount_hold_flag_cursor;
1611       FETCH amount_hold_flag_cursor INTO l_amount_hold_flag;
1612       CLOSE amount_hold_flag_cursor;
1613 
1614       RETURN (l_amount_hold_flag);
1615 
1616     END get_amount_hold_flag;
1617 
1618 /*=============================================================================
1619  |  FUNCTION - get_vendor_hold_flag
1620  |
1621  |  DESCRIPTION
1622  |      returns a flag designating whether an invoice has unreleased vendor
1623  |      holds We've declared a server-side function that can be accessed from
1624  |      our invoices view so as to improve performance when retrieving invoices
1625  |      in the Invoice Gateway.
1626  |
1627  |  KNOWN ISSUES:
1628  |
1629  |  NOTES:
1630  |
1631  |  MODIFICATION HISTORY
1632  |  Date         Author             Description of Change
1633  |
1634  *============================================================================*/
1635     FUNCTION get_vendor_hold_flag(l_invoice_id IN NUMBER)
1636     RETURN VARCHAR2
1637     IS
1638       --Bugfix: 3854385
1639       l_vendor	varchar2(20) := 'VENDOR';
1640       l_vendor_hold_flag  VARCHAR2(1) := 'N';
1641 
1642       cursor vendor_hold_flag_cursor is
1643       SELECT 'Y'
1644         FROM ap_holds
1645        WHERE invoice_id = l_invoice_id
1646          AND hold_lookup_code = l_vendor
1647          AND release_lookup_code IS NULL;
1648 
1649     BEGIN
1650       OPEN vendor_hold_flag_cursor;
1651       FETCH vendor_hold_flag_cursor INTO l_vendor_hold_flag;
1652       CLOSE vendor_hold_flag_cursor;
1653 
1654       RETURN (l_vendor_hold_flag);
1655 
1656     END get_vendor_hold_flag;
1657 
1658 /*=============================================================================
1659  |  FUNCTION - get_similar_drcr_memo
1660  |
1661  |  DESCRIPTION
1662  |      returns the invoice_num of an credit/debit memo that has the same
1663  |      vendor, vendor_site, currency, and amount as the debit/credit memo
1664  |      being validated. If this is a CREDIT then look for a similar DEBIT memo
1665  |      If this is a DEBIT then look for a similar CREDIT memo. This is to try
1666  |      and catch the case when the user enters a DEBIT for some returned
1667  |      goods and then the vendor sends a DEBIT memo for the same return
1668  |
1669  |  KNOWN ISSUES:
1670  |
1671  |  NOTES:
1672  |
1673  |  MODIFICATION HISTORY
1674  |  Date         Author             Description of Change
1675  |
1676  *============================================================================*/
1677 
1678     FUNCTION get_similar_drcr_memo(
1679                  P_vendor_id                IN number,
1680                  P_vendor_site_id           IN number,
1681                  P_invoice_amount           IN number,
1682                  P_invoice_type_lookup_code IN varchar2,
1683                  P_invoice_currency_code    IN varchar2,
1684                  P_calling_sequence         IN varchar2) RETURN varchar2
1685     IS
1686       CURSOR similar_memo_cursor IS
1687       SELECT invoice_num
1688         FROM ap_invoices
1689        WHERE vendor_id = P_vendor_id
1690          AND vendor_site_id = P_vendor_site_id
1691          AND invoice_amount = P_invoice_amount
1692          AND invoice_currency_code = P_invoice_currency_code
1693          AND invoice_type_lookup_code =
1694                  DECODE(P_invoice_type_lookup_code,
1695                         'CREDIT','DEBIT',
1696                         'DEBIT','CREDIT');
1697 
1698       l_invoice_num               ap_invoices.invoice_num%TYPE;
1699       current_calling_sequence    VARCHAR2(2000);
1700       debug_info                  VARCHAR2(100);
1701 
1702     BEGIN
1703 
1704       current_calling_sequence := 'AP_INVOICES_PKG.get_similar_drcr_memo<-'||
1705                                    P_calling_sequence;
1706 
1707       debug_info := 'Open cursor similar_memo_cursor';
1708 
1709       OPEN similar_memo_cursor;
1710       FETCH similar_memo_cursor
1711        INTO l_invoice_num;
1712 
1713       debug_info := 'Close cursor similar_memo_cursor';
1714 
1715       CLOSE similar_memo_cursor;
1716 
1717       RETURN(l_invoice_num);
1718 
1719     EXCEPTION
1720       WHEN OTHERS THEN
1721         IF (SQLCODE <> -20001) THEN
1722           FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
1723           FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1724           FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE',
1725                     current_calling_sequence);
1726           FND_MESSAGE.SET_TOKEN('PARAMETERS',
1727               'P_vendor_id = '                 ||P_vendor_id
1728             ||', P_vendor_site_id = '          ||P_vendor_site_id
1729             ||', P_invoice_amount = '          ||P_invoice_amount
1730             ||', P_invoice_type_lookup_code = '||P_invoice_type_lookup_code
1731             ||', P_invoice_currency_code = '   ||P_invoice_currency_code
1732                                     );
1733            FND_MESSAGE.SET_TOKEN('DEBUG_INFO',debug_info);
1734         END IF;
1735         APP_EXCEPTION.RAISE_EXCEPTION;
1736     END get_similar_drcr_memo;
1737 
1738 /*=============================================================================
1739  |  FUNCTION - eft_bank_details_exist
1740  |
1741  |  DESCRIPTION
1742  |      returns TRUE if the bank details needed for payment method EFT are
1743  |      present for a particular vendor site. Function returns FALSE otherwise.
1744  |
1745  |  KNOWN ISSUES:
1746  |
1747  |  NOTES:
1748  |
1749  |  MODIFICATION HISTORY
1750  |  Date         Author             Description of Change
1751  |
1752  *============================================================================*/
1753 
1754     FUNCTION eft_bank_details_exist (
1755                  P_vendor_site_id   IN number,
1756                  P_calling_sequence IN varchar2) RETURN boolean
1757     IS
1758 
1759       l_vendor_id    number;
1760       l_ext_bank_acct_id number;
1761       current_calling_sequence    VARCHAR2(2000);
1762       debug_info                  VARCHAR2(100);
1763 
1764     BEGIN
1765 
1766       current_calling_sequence := 'AP_INVOICES_Utility_PKG.eft_bank_details_exist<-'||
1767                                   P_calling_sequence;
1768 
1769       debug_info := 'Call AP IBY API';
1770 
1771       SELECT vendor_id
1772       INTO l_vendor_id
1773       FROM PO_VENDOR_SITES_ALL
1774       WHERE vendor_site_id = P_vendor_site_id;
1775 
1776       l_ext_bank_acct_id := AP_IBY_UTILITY_PKG.Get_Default_Iby_Bank_Acct_Id
1777                            (x_vendor_id => l_vendor_id,
1778                             x_vendor_site_id =>  p_vendor_site_id,
1779                             x_payment_function => NULL,
1780                             x_org_id => NULL,
1781                             x_currency_code => NULL,
1782                             x_calling_sequence => 'Ap_Invoices_Utility_Pkg');
1783 
1784       IF l_ext_bank_acct_id IS NOT NULL THEN
1785         RETURN True;
1786       ELSE
1787         RETURN False;
1788       END IF;
1789 
1790     EXCEPTION
1791       WHEN OTHERS THEN
1792         IF (SQLCODE <> -20001) THEN
1793           FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
1794           FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1795           FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1796           FND_MESSAGE.SET_TOKEN('PARAMETERS',
1797             'P_vendor_site_id = '||P_vendor_site_id);
1798           FND_MESSAGE.SET_TOKEN('DEBUG_INFO',debug_info);
1799         END IF;
1800         APP_EXCEPTION.RAISE_EXCEPTION;
1801     END eft_bank_details_exist;
1802 
1803 /*=============================================================================
1804  |  FUNCTION - eft_bank_curr_details_exist
1805  |
1806  |  DESCRIPTION
1807  |      returns TRUE if the bank details (including the matching currency code)
1808  |      needed for payment method EFT are present for a particular vendor
1809  |      site. Function returns FALSE otherwise.
1810  |
1811  |  KNOWN ISSUES:
1812  |
1813  |  NOTES:
1814  |
1815  |  MODIFICATION HISTORY
1816  |  Date         Author             Description of Change
1817  |
1818  *============================================================================*/
1819 
1820     FUNCTION eft_bank_curr_details_exist (
1821                  P_vendor_site_id   IN number,
1822                  P_currency_code    IN varchar2,
1823                  P_calling_sequence IN varchar2) RETURN boolean
1824     IS
1825 
1826       l_vendor_id    number;
1827       l_ext_bank_acct_id number;
1828       current_calling_sequence    VARCHAR2(2000);
1829       debug_info                  VARCHAR2(100);
1830 
1831     BEGIN
1832 
1833       current_calling_sequence := 'AP_INVOICES_Utility_PKG.eft_bank_details_exist<-'||
1834                                   P_calling_sequence;
1835 
1836       debug_info := 'Call AP IBY API';
1837 
1838       SELECT vendor_id
1839       INTO l_vendor_id
1840       FROM PO_VENDOR_SITES_ALL
1841       WHERE vendor_site_id = P_vendor_site_id;
1842 
1843       l_ext_bank_acct_id := AP_IBY_UTILITY_PKG.Get_Default_Iby_Bank_Acct_Id
1844                             (x_vendor_id => l_vendor_id,
1845                             x_vendor_site_id =>  p_vendor_site_id,
1846                             x_payment_function => NULL,
1847                             x_org_id => NULL,
1848                             x_currency_code => NULL,
1849                             x_calling_sequence => 'Ap_Invoices_Utility_Pkg');
1850 
1851       IF l_ext_bank_acct_id IS NOT NULL THEN
1852         RETURN True;
1853       ELSE
1854         RETURN False;
1855       END IF;
1856 
1857     EXCEPTION
1858       WHEN OTHERS THEN
1859         IF (SQLCODE <> -20001) THEN
1860           FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
1861           FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
1862           FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
1863           FND_MESSAGE.SET_TOKEN('PARAMETERS',
1864               'P_vendor_site_id = '||P_vendor_site_id);
1865           FND_MESSAGE.SET_TOKEN('DEBUG_INFO',debug_info);
1866         END IF;
1867         APP_EXCEPTION.RAISE_EXCEPTION;
1868     END eft_bank_curr_details_exist;
1869 
1870      -----------------------------------------------------------------------
1871      -- Function selected_for_payment_flag returns 'Y' if an invoice
1872      -- has been selected for payment; function returns 'N' otherwise.
1873      -----------------------------------------------------------------------
1874 
1875 /*=============================================================================
1876  |  FUNCTION - selected_for_payment_flag
1877  |
1878  |  DESCRIPTION
1879  |      returns 'Y' if an invoice has been selected for payment; function
1880  |      returns 'N' otherwise.
1881  |
1882  |  KNOWN ISSUES:
1883  |
1884  |  NOTES:
1885  |
1886  |  MODIFICATION HISTORY
1887  |  Date         Author             Description of Change
1888  |
1889  *============================================================================*/
1890 
1891     FUNCTION selected_for_payment_flag (P_invoice_id IN number)
1892     RETURN varchar2
1893     IS
1894       l_flag varchar2(1) := 'N';
1895       CURSOR selected_for_payment_cursor IS
1896       SELECT 'Y'
1897         FROM   AP_SELECTED_INVOICES
1898        WHERE  invoice_id = P_invoice_id
1899       UNION
1900       SELECT 'Y'
1901         FROM AP_PAYMENT_SCHEDULES_ALL
1902         WHERE invoice_id = P_invoice_id
1903         AND checkrun_id IS NOT NULL;
1904 
1905     BEGIN
1906 
1907        OPEN selected_for_payment_cursor;
1908       FETCH selected_for_payment_cursor
1909        INTO l_flag;
1910       CLOSE selected_for_payment_cursor;
1911 
1912       RETURN(l_flag);
1913 
1914     END selected_for_payment_flag;
1915 
1916 /*=============================================================================
1917  |  FUNCTION - get_discount_pay_dists_flag
1918  |
1919  |  DESCRIPTION
1920  |      returns 'Y' if there are any payment distributions associated with an
1921  |      invoice which are of type DISCOUNT.
1922  |
1923  |  KNOWN ISSUES:
1924  |
1925  |  NOTES:
1926  |
1927  |  MODIFICATION HISTORY
1928  |  Date         Author             Description of Change
1929  |
1930  *============================================================================*/
1931 
1932     FUNCTION get_discount_pay_dists_flag (P_invoice_id IN number)
1933     RETURN varchar2
1934     IS
1935       l_flag varchar2(1) := 'N';
1936 
1937       CURSOR payment_cursor IS
1938       SELECT 'Y'
1939       FROM   ap_invoice_payments
1940       WHERE  invoice_id = P_invoice_id
1941       AND    nvl(discount_taken,0) <> 0;
1942 
1943     BEGIN
1944 
1945        OPEN payment_cursor;
1946       FETCH payment_cursor
1947        INTO l_flag;
1948       CLOSE payment_cursor;
1949 
1950       RETURN(l_flag);
1951 
1952     END get_discount_pay_dists_flag;
1953 
1954 /*=============================================================================
1955  |  FUNCTION - get_unposted_void_payment
1956  |
1957  |  DESCRIPTION
1958  |       returns 'Y' if an invoice has an unposted payment which is linked to
1959  |       a voided check AND either the Primary or Secondary set of books is
1960  |       'Cash'.
1961  |
1962  |  KNOWN ISSUES:
1963  |
1964  |  NOTES:
1965  |
1966  |  MODIFICATION HISTORY
1967  |  Date         Author             Description of Change
1968  |
1969  *============================================================================*/
1970     FUNCTION get_unposted_void_payment (P_invoice_id IN number)
1971     RETURN varchar2
1972     IS
1973       l_flag     varchar2(1) := 'N';
1974       l_org_id   AP_SYSTEM_PARAMETERS_ALL.ORG_ID%TYPE;
1975 
1976       CURSOR payment_cursor IS
1977       SELECT 'Y', p.org_id
1978         FROM ap_invoice_payments p,
1979              ap_checks c,
1980              ap_system_parameters SP
1981        WHERE  p.invoice_id = P_invoice_id
1982          AND  p.org_id = sp.org_id
1983          AND  nvl(p.cash_posted_flag,'N') <> 'Y'
1984          AND  p.check_id = c.check_id
1985          AND  c.void_date IS NOT NULL
1986          AND  (sp.accounting_method_option = 'Cash' OR
1987                sp.secondary_accounting_method = 'Cash');
1988 
1989     BEGIN
1990 
1991        OPEN payment_cursor;
1992       FETCH payment_cursor
1993        INTO l_flag, l_org_id;
1994       CLOSE payment_cursor;
1995 
1996       RETURN(l_flag);
1997 
1998     END get_unposted_void_payment;
1999 
2000 /*=============================================================================
2001  |  FUNCTION - get_prepayments_applied_flag
2002  |
2003  |  DESCRIPTION
2004  |       returns 'Y' if an invoice has prepayments applied to it.
2005  |
2006  |  KNOWN ISSUES:
2007  |
2008  |  NOTES:
2009  |
2010  |  MODIFICATION HISTORY
2011  |  Date         Author             Description of Change
2012  |
2013  *============================================================================*/
2014 
2015     FUNCTION get_prepayments_applied_flag (P_invoice_id IN number)
2016     RETURN varchar2
2017     IS
2018       l_flag varchar2(1) := 'N';
2019     BEGIN
2020 
2021       IF ( sign (AP_INVOICES_UTILITY_PKG.get_prepay_amount_applied(
2022                         P_invoice_id)) = 1 ) THEN
2023         l_flag := 'Y';
2024       ELSE
2025         l_flag := null;
2026       END IF;
2027 
2028       RETURN (l_flag);
2029 
2030     END get_prepayments_applied_flag;
2031 
2032 /*=============================================================================
2033  |  FUNCTION - get_payments_exist_flag
2034  |
2035  |  DESCRIPTION
2036  |      returns 'Y' if an invoice has corresponding records in
2037  |      ap_invoice_payments
2038  |
2039  |  KNOWN ISSUES:
2040  |
2041  |  NOTES:
2042  |
2043  |  MODIFICATION HISTORY
2044  |  Date         Author             Description of Change
2045  |
2046  *============================================================================*/
2047 
2048     FUNCTION get_payments_exist_flag (P_invoice_id IN number)
2049     RETURN varchar2
2050     IS
2051       l_flag varchar2(1) := 'N';
2052 
2053       CURSOR payments_exist_cursor IS
2054       SELECT 'Y'
2055         FROM ap_invoice_payments
2056        WHERE invoice_id = P_invoice_id;
2057 
2058     BEGIN
2059       OPEN payments_exist_cursor;
2060       FETCH payments_exist_cursor INTO l_flag;
2061       CLOSE payments_exist_cursor;
2062 
2063       RETURN (l_flag);
2064 
2065     END get_payments_exist_flag;
2066 
2067 /*=============================================================================
2068  |  FUNCTION - get_prepay_amount_applied
2069  |
2070  |  DESCRIPTION
2071  |      returns the sum of the applied prepayment amounts for a given
2072  |      prepayment
2073  |
2074  |  KNOWN ISSUES:
2075  |
2076  |  NOTES:
2077  |
2078  |  MODIFICATION HISTORY
2079  |  Date         Author             Description of Change
2080  |
2081  *============================================================================*/
2082 
2083     FUNCTION get_prepay_amount_applied (P_invoice_id IN number)
2084     RETURN number
2085     IS
2086       l_prepay_amount         number := 0;
2087 
2088     BEGIN
2089 
2090       -- eTax Uptake.  This function may be obsolete in the future.
2091       -- for now call ap_prepay_utils_pkg.
2092       l_prepay_amount :=
2093         AP_PREPAY_UTILS_PKG.get_prepay_amount_applied(P_invoice_id);
2094 
2095       RETURN (l_prepay_amount);
2096 
2097     END get_prepay_amount_applied;
2098 
2099 
2100 /*=============================================================================
2101  |  FUNCTION - get_prepay_amount_remaining
2102  |
2103  |  DESCRIPTION
2104  |      returns the sum of the unapplied prepayment amounts for a given
2105  |      prepayment
2106  |
2107  |  KNOWN ISSUES:
2108  |
2109  |  NOTES:
2110  |      Bug 1029985. Including the tax on the prepayment when calculating
2111  |      the prepay_amount_remaining.
2112  |
2113  |  MODIFICATION HISTORY
2114  |  Date         Author             Description of Change
2115  |
2116  *============================================================================*/
2117 
2118     FUNCTION get_prepay_amount_remaining (P_invoice_id IN number)
2119     RETURN number
2120     IS
2121       l_prepay_amount_remaining NUMBER := 0;
2122 
2123     BEGIN
2124       -- eTax Uptake.  This function may be obsolete in the future.
2125       -- for now call ap_prepay_utils_pkg.
2126       l_prepay_amount_remaining :=
2127         AP_PREPAY_UTILS_PKG.get_prepay_amount_remaining(P_invoice_id);
2128 
2129       RETURN(l_prepay_amount_remaining);
2130 
2131     END get_prepay_amount_remaining;
2132 
2133  ---------------------------------------------------------------------------
2134   -- Function get_prepay_amt_rem_set was created for bug 4413272
2135   -- The prepay amount remaining function  was also required to take care
2136   -- of the settlement date while calculating the amount for iexpenses team
2137  -------------------------------------------------------------------------
2138 
2139      FUNCTION get_prepay_amt_rem_set(P_invoice_id IN number)
2140        RETURN number
2141      IS
2142         l_prepay_amount_remaining number:=0;
2143         cursor c_prepay_amount_remaining IS
2144         SELECT SUM(nvl(prepay_amount_remaining,amount))
2145         FROM  ap_invoice_distributions_all aid,ap_invoices_all ai
2146         WHERE aid.invoice_id = P_invoice_id
2147         AND   aid.line_type_lookup_code IN ('ITEM','TAX')
2148         AND   nvl(aid.reversal_flag,'N') <> 'Y'
2149         AND  ai.invoice_id = P_invoice_id
2150         AND  ai.invoice_type_lookup_code = 'PREPAYMENT'
2151         AND  ai.earliest_settlement_date IS NOT NULL
2152         AND  ai.earliest_settlement_date <= trunc(SYSDATE);
2153     BEGIN
2154         OPEN c_prepay_amount_remaining;
2155         FETCH c_prepay_amount_remaining INTO l_prepay_amount_remaining;
2156         CLOSE c_prepay_amount_remaining;
2157         RETURN(l_prepay_amount_remaining);
2158     END get_prepay_amt_rem_set;
2159 
2160 
2161 /*=============================================================================
2162  |  FUNCTION - get_prepayment_type
2163  |
2164  |  DESCRIPTION
2165  |      returns whether prepayment is of type "PERMANENT' which cannot be
2166  |      applied or 'TEMPORARY' which can be applied.
2167  |
2168  |  KNOWN ISSUES:
2169  |
2170  |  NOTES:
2171  |
2172  |  MODIFICATION HISTORY
2173  |  Date         Author             Description of Change
2174  |
2175  *============================================================================*/
2176 
2177     FUNCTION get_prepayment_type (P_invoice_id IN number)
2178     RETURN varchar2
2179     IS
2180       l_prepayment_type VARCHAR2(9);
2181 
2182       CURSOR c_prepayment_type IS
2183       SELECT decode(AI.EARLIEST_SETTLEMENT_DATE,null,'PERMANENT','TEMPORARY')
2184         FROM ap_invoices_all ai
2185        WHERE ai.invoice_id = P_invoice_id;
2186     BEGIN
2187 
2188       OPEN c_prepayment_type;
2189       FETCH c_prepayment_type INTO l_prepayment_type;
2190       CLOSE c_prepayment_type;
2191 
2192       RETURN(l_prepayment_type);
2193     END get_prepayment_type;
2194 
2195 /*=============================================================================
2196  |  FUNCTION - get_packet_id
2197  |
2198  |  DESCRIPTION
2199  |      returns the invoice-level packet_id. If only one unique packet_id
2200  |      exists for all distributions on an invoice, that packet_id is the
2201  |      invoice-level packet_id, otherwise there is none.
2202  |
2203  |  KNOWN ISSUES:
2204  |
2205  |  NOTES:
2206  |
2207  |  MODIFICATION HISTORY
2208  |  Date         Author             Description of Change
2209  |
2210  *============================================================================*/
2211 
2212     FUNCTION get_packet_id (P_invoice_id IN number)
2213     RETURN number
2214     IS
2215       l_packet_id number := '';
2216 
2217       cursor packet_id_cursor is
2218       select decode(count(distinct(packet_id)),1,max(packet_id),'')
2219         from ap_invoice_distributions
2220        where invoice_id = P_Invoice_Id
2221          and packet_id is not null;
2222 
2223     BEGIN
2224       OPEN packet_id_cursor;
2225       FETCH packet_id_cursor INTO l_packet_id;
2226       CLOSE packet_id_cursor;
2227 
2228       RETURN (l_packet_id);
2229 
2230     END get_packet_id;
2231 
2232 /*=============================================================================
2233  |  FUNCTION - get_payment_status
2234  |
2235  |  DESCRIPTION
2236  |      will read through every line of the payment schedules to check the
2237  |      payment_status_flag value. It will return 'Y' if it is fully paid.
2238  |      Other values are 'N' and 'P'
2239  |
2240  |  KNOWN ISSUES:
2241  |
2242  |  NOTES:
2243  |
2244  |  MODIFICATION HISTORY
2245  |  Date         Author             Description of Change
2246  |
2247  *============================================================================*/
2248 
2249     FUNCTION  get_payment_status( p_invoice_id  IN  NUMBER )
2250     RETURN VARCHAR2
2251     IS
2252       l_return_val    VARCHAR2(25);
2253       l_curr_ps_flag  VARCHAR2(25);
2254       temp_ps_flag    VARCHAR2(25);
2255       l_ps_count      NUMBER := 0;
2256 
2257       CURSOR c_select_payment_status (cv_invoice_id NUMBER ) IS
2258       SELECT payment_status_flag
2259         FROM ap_payment_schedules
2260        WHERE invoice_id = cv_invoice_id;
2261 
2262     BEGIN
2263 
2264       OPEN c_select_payment_status ( p_invoice_id );
2265       LOOP
2266       FETCH c_select_payment_status into temp_ps_flag;
2267       EXIT when c_select_payment_status%NOTFOUND;
2268         l_ps_count := l_ps_count +1;
2269 
2270         IF ( l_ps_count = 1 ) THEN
2271           l_curr_ps_flag := temp_ps_flag;
2272         ELSE
2273           IF ( l_curr_ps_flag <> temp_ps_flag ) THEN
2274             l_curr_ps_flag := 'P';
2275              EXIT;
2276           ELSE
2277             l_curr_ps_flag := temp_ps_flag;
2278           END IF; -- END of l_curr_ps_flag check
2279         END IF; -- END of l_ps_count  check
2280       END LOOP;
2281       CLOSE c_select_payment_status;
2282 
2283       IF ( l_ps_count > 0 ) THEN
2284         l_return_val := l_curr_ps_flag;
2285       ELSE
2286         l_return_val := 'N';
2287       END IF;
2288       RETURN (l_return_val );
2289 
2290     END get_payment_status;
2291 
2292 /*=============================================================================
2293  |  FUNCTION - is_inv_pmt_prepay_posted
2294  |
2295  |  DESCRIPTION
2296  |      returns TRUE if an invoice has been paid/prepaid and accounting has
2297  |      been done for payment/reconciliation or prepayment accordingly.
2298  |
2299  |  KNOWN ISSUES:
2300  |
2301  |  NOTES:
2302  |
2303  |  MODIFICATION HISTORY
2304  |  Date         Author             Description of Change
2305  |
2306  *============================================================================*/
2307 
2308     FUNCTION is_inv_pmt_prepay_posted(
2309                  P_invoice_id             IN NUMBER,
2310                  P_org_id                 IN NUMBER,
2311                  P_discount_taken         IN NUMBER,
2312                  P_prepaid_amount         IN NUMBER,
2313                  P_automatic_offsets_flag IN VARCHAR2,
2314                  P_discount_dist_method   IN VARCHAR2,
2315                  P_payment_status_flag    IN VARCHAR2)
2316     RETURN BOOLEAN
2317     IS
2318       l_count_pmt_posted       NUMBER := 0;
2319       l_count_pmt_hist_posted  NUMBER := 0;
2320       l_count_prepaid_posted   NUMBER := 0;
2321       l_primary_acctg_method   VARCHAR2(25);
2322       l_secondary_acctg_method VARCHAR2(25);
2323       l_org_id                 AP_SYSTEM_PARAMETERS_ALL.ORG_ID%TYPE;
2324     BEGIN
2325 
2326       select asp.accounting_method_option,
2327              nvl(asp.secondary_accounting_method, 'None'),
2328              asp.org_id
2329         into l_primary_acctg_method,
2330              l_secondary_acctg_method,
2331              l_org_id
2332         from ap_system_parameters_all asp
2333         where asp.org_id = P_org_id;
2334 
2335 
2336     /*-----------------------------------------------------------------+
2337      |  If the invoice has been fully or partially paid and any of the |
2338      |  following is true, then check for accounting of the payment:   |
2339      |  1. Auto offsets is on                                          |
2340      |  2. Running cash basis                                          |
2341      |  3. There was a discount and the discount method is other than  |
2342      |     system                                                      |
2343      +-----------------------------------------------------------------*/
2344 
2345 
2346       IF ((p_payment_status_flag <> 'N') AND
2347           ((nvl(p_automatic_offsets_flag, 'N') = 'Y') OR
2348           (l_primary_acctg_method = 'Cash')          OR
2349           (l_secondary_acctg_method = 'Cash')        OR
2350           ((nvl(p_discount_taken, 0) <> 0) AND
2351           (nvl(p_discount_dist_method, 'EXPENSE') <> 'SYSTEM')))) THEN
2352 
2353         select count(*)
2354           into l_count_pmt_posted
2355           from ap_invoice_payments aip
2356          where aip.posted_flag = 'Y'
2357            and aip.invoice_id = p_invoice_id;
2358 
2359         select count(*)
2360           into l_count_pmt_hist_posted
2361           from ap_payment_history aph
2362          where aph.posted_flag = 'Y'
2363            and aph.check_id in (select check_id
2364                                   from ap_invoice_payments aip
2365                                  where aip.invoice_id = p_invoice_id);
2366 
2367       END IF;
2368 
2369     /*-----------------------------------------------------------------+
2370      |  If a prepayment has been applied against the invoice and       |
2371      |  any of the following is true, then check for accounting of     |
2372      |  the prepayment application:                                    |
2373      |  1. Auto offsets is on                                          |
2374      |  2. Running cash basis                                          |
2375      +-----------------------------------------------------------------*/
2376 
2377       IF ((nvl(p_prepaid_amount, 0) <> 0) AND
2378           (nvl(p_automatic_offsets_flag, 'N') = 'Y' OR
2379            l_primary_acctg_method = 'Cash' OR
2380            l_secondary_acctg_method = 'Cash')) THEN
2381 
2382         select count(*)
2383           into l_count_prepaid_posted
2384           from ap_invoice_distributions aid
2385          where aid.posted_flag <> 'N'
2386            and aid.invoice_id = p_invoice_id
2387            and aid.line_type_lookup_code = 'PREPAY';
2388       END IF;
2389 
2390       IF (l_count_pmt_posted <> 0 OR
2391           l_count_pmt_hist_posted <> 0 OR
2392           l_count_prepaid_posted <> 0) THEN
2393         RETURN TRUE;
2394       ELSE
2395         RETURN FALSE;
2396       END IF;
2397 
2398     END is_inv_pmt_prepay_posted;
2399 
2400 
2401 /*=============================================================================
2402  |  FUNCTION - get_pp_amt_applied_on_date
2403  |
2404  |  DESCRIPTION
2405  |      returns the sum of the applied prepayment amounts to an invoice by a
2406  |      prepayment for a given date. This has been added to fix the bug 977563
2407  |
2408  |  KNOWN ISSUES:
2409  |
2410  |  NOTES:
2411  |
2412  |  MODIFICATION HISTORY
2413  |  Date         Author             Description of Change
2414  |
2415  *============================================================================*/
2416 
2417     FUNCTION get_pp_amt_applied_on_date (
2418                  P_invoice_id       IN NUMBER,
2419                  P_prepay_id        IN NUMBER,
2420                  P_application_date IN DATE)
2421     RETURN number
2422     IS
2423       l_prepay_amt_applied NUMBER := 0;
2424 
2425     BEGIN
2426 
2427       SELECT SUM(aid1.amount * -1)
2428         INTO l_prepay_amt_applied
2429         FROM ap_invoice_distributions aid1, ap_invoice_distributions aid2
2430        WHERE aid1.invoice_id = P_invoice_id
2431          AND aid1.line_type_lookup_code = 'PREPAY'
2432          AND aid1.prepay_distribution_id = aid2.invoice_distribution_id
2433          AND aid2.invoice_id = P_prepay_id
2434          AND aid2.last_update_date = P_application_date ;
2435 
2436       RETURN (l_prepay_amt_applied);
2437 
2438     END get_pp_amt_applied_on_date;
2439 
2440 /*=============================================================================
2441  |  FUNCTION - get_dist_count
2442  |
2443  |  DESCRIPTION
2444  |      returns the count of distributions available for the given invoice_id.
2445  |
2446  |  KNOWN ISSUES:
2447  |
2448  |  NOTES
2449  |      The same function is added as an enhancement to the Key indicators
2450  |      report. The bug for the same is 1728036.
2451  |
2452  |  MODIFICATION HISTORY
2453  |  Date         Author             Description of Change
2454  |
2455  *============================================================================*/
2456 
2457     FUNCTION get_dist_count (p_invoice_id IN NUMBER)
2458     RETURN NUMBER
2459     IS
2460       l_count_distributions NUMBER;
2461     BEGIN
2462 
2463       SELECT count(invoice_distribution_id)
2464         INTO l_count_distributions
2465         FROM ap_invoice_distributions
2466        WHERE invoice_id = p_invoice_id;
2467 
2468       RETURN l_count_distributions;
2469 
2470     EXCEPTION
2471     WHEN others THEN
2472       RETURN 0;
2473     END get_dist_count;
2474 
2475 
2476 /*=============================================================================
2477  |  FUNCTION - get_amt_applied_per_prepay
2478  |
2479  |  DESCRIPTION
2480  |      returns the sum of the applied prepayment amounts to an invoice by a
2481  |      prepayment. This has been added to do not use a new select statement in
2482  |      the expense report import program.
2483  |
2484  |  KNOWN ISSUES:
2485  |
2486  |  NOTES:
2487  |
2488  |  MODIFICATION HISTORY
2489  |  Date         Author             Description of Change
2490  |
2491  *===========================================================================*/
2492 
2493     FUNCTION get_amt_applied_per_prepay (
2494                  P_invoice_id          IN NUMBER,
2495                  P_prepay_id           IN NUMBER)
2496     RETURN number
2497     IS
2498       l_prepay_amt_applied NUMBER := 0;
2499 
2500     BEGIN
2501 
2502       SELECT SUM(aid1.amount * -1)
2503         INTO l_prepay_amt_applied
2504         FROM ap_invoice_distributions aid1, ap_invoice_distributions aid2
2505        WHERE aid1.invoice_id = P_invoice_id
2506          AND aid1.line_type_lookup_code = 'PREPAY'
2507          AND aid1.prepay_distribution_id = aid2.invoice_distribution_id
2508          AND aid2.invoice_id = P_prepay_id;
2509 
2510       RETURN (l_prepay_amt_applied);
2511 
2512     END get_amt_applied_per_prepay;
2513 
2514 /*=============================================================================
2515  |  FUNCTION - get_explines_count
2516  |
2517  |  DESCRIPTION
2518  |      added to get the count of expense report lines for a given expense
2519  |      report header id. This function was added for the enhancement to the
2520  |      key indicators report.
2521  |
2522  |  KNOWN ISSUES:
2523  |
2524  |  NOTES:
2525  |      Bug 2298873 Code added by MSWAMINA.
2526  |
2527  |  MODIFICATION HISTORY
2528  |  Date         Author             Description of Change
2529  |
2530  *===========================================================================*/
2531     FUNCTION get_explines_count (p_expense_report_id IN NUMBER)
2532     RETURN NUMBER
2533     IS
2534       l_explines_count NUMBER;
2535     BEGIN
2536 
2537       SELECT count(*)
2538       INTO   l_explines_count
2539       FROM   ap_expense_report_lines
2540       WHERE  report_header_id = p_expense_report_id;
2541 
2542       RETURN l_explines_count;
2543 
2544     EXCEPTION
2545       WHEN OTHERS THEN
2546         l_explines_count := 0;
2547         RETURN l_explines_count;
2548     END get_explines_count;
2549 
2550 
2551 /*=============================================================================
2552  |  FUNCTION - get_expense_type
2553  |
2554  |  DESCRIPTION
2555  |      added to decide whether the information is available in in expense
2556  |      reports table as well as in ap invoices or only in ap invoices
2557  |
2558  |  KNOWN ISSUES:
2559  |
2560  |  NOTES
2561  |      If the information is available in both the table we should get the
2562  |      information from ap expense report headers, if not we should get the
2563  |      information from ap invoices. This was added based on the requirement
2564  |      from GSI and confirmed by lauren
2565  |
2566  |  MODIFICATION HISTORY
2567  |  Date         Author             Description of Change
2568  |
2569  *===========================================================================*/
2570 
2571     FUNCTION get_expense_type (
2572                  p_source in varchar2,
2573                  p_invoice_id in number)
2574     RETURN varchar2
2575     IS
2576       l_return_type VARCHAR2(1);
2577     BEGIN
2578 
2579       IF p_source IN ('XpenseXpress', 'SelfService') THEN
2580 
2581         SELECT 'E'
2582         INTO   l_return_type
2583         FROM   ap_expense_report_headers aerh
2584         WHERE  aerh.vouchno = p_invoice_id;
2585 
2586       ELSE
2587 
2588         l_return_type := 'I';
2589 
2590       END IF;
2591 
2592       RETURN l_return_type;
2593 
2594     EXCEPTION
2595       WHEN NO_DATA_FOUND THEN
2596         l_return_type := 'I';
2597         RETURN l_return_type;
2598       WHEN OTHERS THEN
2599         l_return_type := 'I';
2600         RETURN l_return_type;
2601 
2602     END get_expense_type;
2603 
2604 /*=============================================================================
2605  |  FUNCTION - get_max_inv_line_num
2606  |
2607  |  DESCRIPTION
2608  |      returns the highest line number of invoice lines belonging to
2609  |      invoice P_invoice_id
2610  |
2611  |  KNOWN ISSUES
2612  |
2613  |  NOTES
2614  |
2615  |  MODIFICATION HISTORY
2616  |  Date         Author             Description of Change
2617  |
2618  *===========================================================================*/
2619 
2620     FUNCTION GET_MAX_INV_LINE_NUM(P_invoice_id IN NUMBER)
2621     RETURN NUMBER
2622     IS
2623       l_max_inv_line_num NUMBER := 0;
2624     BEGIN
2625 
2626       SELECT nvl( MAX(line_number),0 )
2627         INTO l_max_inv_line_num
2628         FROM ap_invoice_lines
2629        WHERE invoice_id = P_invoice_id;
2630 
2631       RETURN (l_max_inv_line_num);
2632 
2633     END GET_MAX_INV_LINE_NUM;
2634 
2635 
2636 /*=============================================================================
2637  |  FUNCTION - get_line_total
2638  |
2639  |  DESCRIPTION
2640  |      returns the total invoice line amount for the invoice.
2641  |
2642  |  KNOWN ISSUES:
2643  |
2644  |  NOTES:
2645  |
2646  |  MODIFICATION HISTORY
2647  |  Date         Author             Description of Change
2648  |
2649  *===========================================================================*/
2650 
2651     FUNCTION GET_LINE_TOTAL(P_invoice_id IN NUMBER)
2652     RETURN NUMBER
2653     IS
2654       line_total NUMBER := 0;
2655     BEGIN
2656 
2657        -- eTax uptake.   Included condition to know if a TAX line is
2658        -- Do not include prepayment application amount if the prepayment
2659        -- is not included in the invoice.  (invoice_includes_prepay_flag = N)
2660 
2661        SELECT SUM(NVL(amount,0))
2662          INTO line_total
2663          FROM ap_invoice_lines ail
2664         WHERE ail.invoice_id = p_invoice_id
2665           AND ((ail.line_type_lookup_code not in ('PREPAY','AWT') --Bug 7372061 Excluded 'AWT' amount from the total line amount.
2666                AND ail.prepay_invoice_id IS NULL
2667                AND ail.prepay_line_number IS NULL)
2668                OR nvl(ail.invoice_includes_prepay_flag,'N') = 'Y');
2669 
2670       RETURN(line_total);
2671 
2672     END GET_LINE_TOTAL;
2673 
2674 /*=============================================================================
2675  |  FUNCTION - ROUND_BASE_AMTS
2676  |
2677  |  DESCRIPTION
2678  |      returns the rounded base amount if there is any. it returns FALSE if
2679  |      no rounding amount necessary, otherwise it returns TRUE.
2680  |
2681  |  Business Assumption
2682  |      1. Called after base amount of all lines is populated
2683  |      2. Same exchange rate for all the lines
2684  |      3. It will be called by Primary ledger (AP) or Reporting ledger (MRC)
2685  |      4. Returns FALSE if sum of lines amount is different than invoice
2686  |         amount, since in that case the rounding is meaningless.
2687  |
2688  |  PARAMETERS
2689  |      X_Invoice_Id - Invoice Id
2690  |      X_Reporting_Ledger_Id - For ALC/MRC use only.
2691  |      X_Rounded_Line_Numbers - returns the line numbers that can be adjusted
2692  |      X_Rounded_Amt - rounded amount
2693  |      X_Debug_Info - debug information
2694  |      X_Debug_Context - error context
2695  |      X_Calling_Sequence - debug usage
2696  |
2697  |  KNOWN ISSUES:
2698  |
2699  |  NOTES:
2700  |
2701  |  MODIFICATION HISTORY
2702  |  Date         Author             Description of Change
2703  |  19-MAY-2008  KPASIKAN           modified for 6892789 to get the lines that
2704  |                                  can be adjusted
2705  *============================================================================*/
2706 
2707     FUNCTION round_base_amts(
2708                        X_Invoice_Id          IN NUMBER,
2709                        X_Reporting_Ledger_Id IN NUMBER DEFAULT NULL,
2710                        X_Rounded_Line_Numbers OUT NOCOPY inv_line_num_tab_type,
2711                        X_Rounded_Amt         OUT NOCOPY NUMBER,
2712                        X_Debug_Info          OUT NOCOPY VARCHAR2,
2713                        X_Debug_Context       OUT NOCOPY VARCHAR2,
2714                        X_Calling_sequence    IN VARCHAR2)
2715     RETURN BOOLEAN IS
2716     l_rounded_amt             NUMBER := 0;
2717     l_rounded_line_numbers    inv_line_num_tab_type;
2718     l_base_currency_code      ap_system_parameters.base_currency_code%TYPE;
2719     l_base_amount             ap_invoices.base_amount%TYPE;
2720     l_invoice_amount          ap_invoices.invoice_amount%TYPE;
2721     l_invoice_currency_code   ap_invoices.invoice_currency_code%TYPE;
2722     l_reporting_currency_code ap_invoices.invoice_currency_code%TYPE;
2723     l_sum_base_amt            NUMBER;
2724     l_sum_amt                 NUMBER;
2725     l_sum_rpt_base_amt        NUMBER;
2726 
2727     current_calling_sequence VARCHAR2(2000);
2728     debug_info               VARCHAR2(100);
2729 
2730     cursor invoice_cursor is
2731       -- inv_base_amt/rep_base_amt
2732       SELECT decode(x_reporting_ledger_id, null, AI.base_amount, null),
2733              AI.invoice_amount, -- invoice amount
2734              AI.invoice_currency_code, -- invoice_currency_code
2735              ASP.base_currency_code -- base_currency_code
2736         FROM ap_invoices AI, ap_system_parameters ASP
2737        WHERE AI.invoice_id = X_invoice_id
2738          AND ASP.org_id = AI.org_id;
2739 
2740   BEGIN
2741 
2742     current_calling_sequence := 'AP_INVOICES_UTILITY_PKG - Round_Base_Amt ' ||
2743                                 X_calling_sequence;
2744 
2745     -------------------------------------------------------------
2746     debug_info := 'Round_Base_Amt - Open cursor invoice_cursor';
2747     -------------------------------------------------------------
2748 
2749     OPEN invoice_cursor;
2750     FETCH invoice_cursor
2751       INTO l_base_amount,
2752            l_invoice_amount,
2753            l_invoice_currency_code,
2754            l_base_currency_code;
2755     IF (invoice_cursor%NOTFOUND) THEN
2756       CLOSE invoice_cursor;
2757       RAISE NO_DATA_FOUND;
2758     END IF;
2759     CLOSE invoice_cursor;
2760 
2761     IF (X_Reporting_Ledger_Id IS NULL) THEN
2762       --------------------------------------------------------------------
2763       debug_info := 'Round_base_amt Case 1 - Rounding for primary ledger';
2764       --------------------------------------------------------------------
2765 
2766       IF (l_invoice_currency_code <> l_base_currency_code) THEN
2767         BEGIN
2768           SELECT SUM(base_amount), SUM(amount)
2769             INTO l_sum_base_amt, l_sum_amt
2770             FROM ap_invoice_lines AIL
2771            WHERE AIL.invoice_id = X_INVOICE_ID
2772              AND line_type_lookup_code <> 'AWT'
2773              AND (invoice_includes_prepay_flag = 'Y' OR
2774                  line_type_lookup_code <> 'PREPAY');
2775           --  eTax: Tax lines that do not contribute to lines total
2776           --  should be excluded.
2777         END;
2778 
2779         IF (l_sum_amt = l_invoice_amount) THEN
2780           l_rounded_amt := l_base_amount - l_sum_base_amt;
2781         ELSE
2782           X_ROUNDED_AMT      := 0;
2783           X_Rounded_Line_Numbers.delete;
2784           X_debug_context    := current_calling_sequence;
2785           X_debug_info       := debug_info;
2786           RETURN(FALSE);
2787         END IF;
2788       ELSE
2789         ---------------------------------------------------------------------
2790         debug_info := 'Round_Base_Amt - same inv currency/base currency';
2791         ---------------------------------------------------------------------
2792         X_ROUNDED_AMT      := 0;
2793         X_Rounded_Line_Numbers.delete;
2794         X_debug_context    := current_calling_sequence;
2795         X_debug_info       := debug_info;
2796         RETURN(FALSE);
2797       END IF; -- end of check currency for primary
2798 
2799     ELSE
2800 
2801       Null; -- Removed the code here due to MRC obsoletion
2802 
2803     END IF; -- end of check x_reporting_ledger_id
2804 
2805     IF (l_rounded_amt <> 0) THEN
2806       --------------------------------------------------------------------
2807       debug_info := 'Round_Base_Amt - round amt exists and find the line';
2808       --------------------------------------------------------------------
2809       BEGIN
2810 
2811         SELECT ail1.line_number
2812           BULK COLLECT INTO l_Rounded_Line_Numbers
2813           FROM ap_invoice_lines ail1
2814          WHERE ail1.invoice_id = X_invoice_id
2815            AND ail1.amount <> 0
2816            AND (EXISTS
2817                 (SELECT 'UNPOSTED'
2818                    FROM ap_invoice_distributions D1
2819                   WHERE D1.invoice_id = ail1.invoice_id
2820                     AND D1.invoice_line_number = ail1.line_number
2821                     AND NVL(D1.posted_flag, 'N') = 'N') OR
2822                 (NOT EXISTS
2823                  (SELECT 'X'
2824                     FROM ap_invoice_distributions D2
2825                    WHERE D2.invoice_id = ail1.invoice_id
2826                      AND D2.invoice_line_number = ail1.line_number)))
2827           ORDER BY ail1.base_amount desc;
2828 
2829       END;
2830 
2831       X_ROUNDED_AMT      := l_rounded_amt;
2832       X_Rounded_Line_Numbers := l_rounded_line_numbers;
2833       X_debug_context    := current_calling_sequence;
2834       X_debug_info       := debug_info;
2835       RETURN(TRUE);
2836     ELSE
2837       ---------------------------------------------------------------------
2838       debug_info := 'Round_Base_Amt - round_amt is 0 ';
2839       ---------------------------------------------------------------------
2840       X_ROUNDED_AMT      := 0;
2841       X_Rounded_Line_Numbers.delete;
2842       X_debug_context    := current_calling_sequence;
2843       X_debug_info       := debug_info;
2844       RETURN(FALSE);
2845     END IF; -- end of check l_rounded_amt
2846 
2847   EXCEPTION
2848     WHEN OTHERS THEN
2849       if (SQLCODE <> -20001) then
2850         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
2851         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
2852         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
2853         FND_MESSAGE.SET_TOKEN('PARAMETERS',
2854                               'Invoice Id = ' || X_Invoice_Id);
2855         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
2856       end if;
2857       debug_info      := debug_info || 'Error occurred';
2858       X_debug_context := current_calling_sequence;
2859       X_debug_info    := debug_info;
2860       Return(FALSE);
2861   END round_base_amts;
2862 
2863  /*============================================================================
2864  |  FUNCTION - Is_Inv_Credit_Referenced
2865  |
2866  |  DESCRIPTION
2867  |      Added to check if the invoice has a QUICK CREDIT invoice against it or
2868  |      if this invoice has any active (non discard/non cancelled) corrections.
2869  |
2870  |  KNOWN ISSUES
2871  |
2872  |  NOTES
2873  |
2874  |  MODIFICATION HISTORY
2875  |  Date         Author             Description of Change
2876  |
2877  *===========================================================================*/
2878     FUNCTION Is_Inv_Credit_Referenced( P_invoice_id  IN NUMBER )
2879     RETURN BOOLEAN
2880     IS
2881       l_retVal              BOOLEAN := FALSE;
2882       l_active_count        NUMBER;
2883       l_quick_credit_count  NUMBER:=0;
2884     BEGIN
2885 
2886       -- Perf bug 5173995 , removed count(*) from below 2 SQLs
2887       BEGIN
2888         SELECT 1
2889         INTO   l_active_count
2890         FROM   ap_invoice_lines AIL
2891         WHERE  ( NVL( AIL.discarded_flag, 'N' ) <> 'Y' AND
2892                  NVL( AIL.cancelled_flag, 'N' ) <> 'Y' )
2893         AND    AIL.corrected_inv_id = p_invoice_id
2894         AND    ROWNUM = 1 ;
2895       EXCEPTION
2896         WHEN NO_DATA_FOUND THEN
2897           l_active_count := 0;
2898       END;
2899 
2900       BEGIN
2901       --bug 5475668
2902       if (P_invoice_id is not null) then
2903         SELECT 1
2904         INTO   l_quick_credit_count
2905         FROM   ap_invoices AI
2906         WHERE  AI.credited_invoice_id = P_invoice_id
2907         AND  NVL(AI.quick_credit, 'N') = 'Y'
2908         AND  AI.cancelled_date is null
2909         AND  ROWNUM = 1 ;
2910        end if;
2911       EXCEPTION
2912         WHEN NO_DATA_FOUND THEN
2913           l_quick_credit_count := 0;
2914       END;
2915 
2916       IF ( l_active_count <> 0 or l_quick_credit_count <> 0 ) THEN
2917         l_retVal := TRUE;
2918       END IF;
2919 
2920       RETURN l_retVal;
2921     EXCEPTION
2922       WHEN OTHERS THEN
2923         RETURN FALSE;
2924     END Is_Inv_Credit_Referenced;
2925 
2926 /*=============================================================================
2927  |  FUNCTION - Inv_With_PQ_Corrections
2928  |
2929  |  DESCRIPTION
2930  |      This function returns TRUE if the invoice contains price or quantity
2931  |      corrections.  It returns FALSE otherwise.
2932  |
2933  |  PARAMETERS
2934  |      P_Invoice_Id - Invoice Id
2935  |      P_Calling_Sequence - debug usage
2936  |
2937  |  KNOWN ISSUES:
2938  |
2939  |  NOTES:
2940  |
2941  |  MODIFICATION HISTORY
2942  |  Date         Author             Description of Change
2943  |  30-JUL-2003  SYIDNER            Creation
2944  |
2945  *============================================================================*/
2946 
2947   FUNCTION Inv_With_PQ_Corrections(
2948              P_Invoice_Id           IN NUMBER,
2949              P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN
2950 
2951   IS
2952     CURSOR Invoice_Validation IS
2953     SELECT i.invoice_id
2954       FROM ap_invoices_all i
2955      WHERE i.invoice_id = P_Invoice_Id
2956        AND EXISTS
2957            (SELECT il.invoice_id
2958               FROM ap_invoice_lines_all il
2959              WHERE il.invoice_id = i.invoice_id
2960                AND NVL(il.discarded_flag, 'N') <> 'Y'
2961                AND NVL(il.cancelled_flag, 'N') <> 'Y'
2962                AND il.match_type IN ('PRICE_CORRECTION',
2963                                      'QTY_CORRECTION'));
2964 
2965     l_invoice_id               ap_invoices_all.invoice_id%TYPE;
2966     current_calling_sequence   VARCHAR2(4000);
2967     debug_info                 VARCHAR2(240);
2968     l_return_var               BOOLEAN := FALSE;
2969 
2970   BEGIN
2971       current_calling_sequence := 'AP_INVOICES_UTILITY_PKG - Inv_With_PQ_Corrections';
2972 
2973       -------------------------------------------------------------
2974       debug_info := 'Inv_With_PQ_Corrections - Open cursor';
2975       -------------------------------------------------------------
2976       OPEN invoice_validation;
2977       FETCH invoice_validation INTO l_invoice_id;
2978       IF (invoice_validation%NOTFOUND) THEN
2979         CLOSE invoice_validation;
2980         l_invoice_id := null;
2981 
2982       END IF;
2983 
2984       IF ( invoice_validation%ISOPEN ) THEN
2985         CLOSE invoice_validation;
2986       END IF;
2987 
2988       IF (l_invoice_id IS NOT NULL) THEN
2989         l_return_var := TRUE;
2990 
2991       END IF;
2992 
2993    RETURN l_return_var;
2994 
2995   EXCEPTION
2996     WHEN OTHERS THEN
2997       if (SQLCODE <> -20001) then
2998         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
2999         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
3000         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
3001         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||P_Invoice_Id);
3002         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
3003       end if;
3004       debug_info := debug_info || 'Error occurred';
3005 
3006       IF ( invoice_validation%ISOPEN ) THEN
3007         CLOSE invoice_validation;
3008       END IF;
3009 
3010       APP_EXCEPTION.RAISE_EXCEPTION;
3011 
3012   END Inv_With_PQ_Corrections;
3013 
3014 /*=============================================================================
3015  |  FUNCTION -  Inv_With_Prepayments
3016  |
3017  |  DESCRIPTION
3018  |    This function returns TRUE if the invoice contains prepayment applications.
3019  |    It returns FALSE otherwise.
3020  |
3021  |  PARAMETERS
3022  |      X_Invoice_Id - Invoice Id
3023  |      X_Calling_Sequence - debug usage
3024  |
3025  |  KNOWN ISSUES:
3026  |
3027  |  NOTES:
3028  |
3029  |  MODIFICATION HISTORY
3030  |  Date         Author             Description of Change
3031  |  30-JUL-2003  SYIDNER            Creation
3032  |
3033  *============================================================================*/
3034 
3035   FUNCTION Inv_With_Prepayments(
3036              P_Invoice_Id           IN NUMBER,
3037              P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN
3038 
3039   IS
3040     CURSOR Invoice_Validation IS
3041     SELECT i.invoice_id
3042       FROM ap_invoices_all i
3043      WHERE i.invoice_id = P_Invoice_Id
3044        AND EXISTS
3045            (SELECT il.invoice_id
3046               FROM ap_invoice_lines_all il
3047              WHERE il.invoice_id = i.invoice_id
3048               AND il.line_type_lookup_code = 'PREPAY'
3049               AND NVL(il.discarded_flag, 'N') <> 'Y'
3050               AND NVL(il.cancelled_flag, 'N') <> 'Y');
3051 
3052     l_invoice_id               ap_invoices_all.invoice_id%TYPE;
3053     current_calling_sequence   VARCHAR2(4000);
3054     debug_info                 VARCHAR2(240);
3055     l_return_var               BOOLEAN := FALSE;
3056 
3057   BEGIN
3058       current_calling_sequence := 'AP_INVOICES_UTILITY_PKG - Inv_With_Prepayments';
3059 
3060       -------------------------------------------------------------
3061       debug_info := 'Inv_With_Prepayments - Open cursor';
3062       -------------------------------------------------------------
3063       OPEN invoice_validation;
3064       FETCH invoice_validation INTO l_invoice_id;
3065       IF (invoice_validation%NOTFOUND) THEN
3066         CLOSE invoice_validation;
3067         l_invoice_id := null;
3068 
3069       END IF;
3070 
3071       IF ( invoice_validation%ISOPEN ) THEN
3072         CLOSE invoice_validation;
3073       END IF;
3074 
3075       IF (l_invoice_id IS NOT NULL) THEN
3076         l_return_var := TRUE;
3077 
3078       END IF;
3079 
3080    RETURN l_return_var;
3081 
3082   EXCEPTION
3083     WHEN OTHERS THEN
3084       if (SQLCODE <> -20001) then
3085         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
3086         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
3087         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
3088         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||P_Invoice_Id);
3089         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
3090       end if;
3091       debug_info := debug_info || 'Error occurred';
3092 
3093       IF ( invoice_validation%ISOPEN ) THEN
3094         CLOSE invoice_validation;
3095       END IF;
3096 
3097       APP_EXCEPTION.RAISE_EXCEPTION;
3098 
3099   END Inv_With_Prepayments;
3100 
3101 /*=============================================================================
3102  |  FUNCTION - Invoice_Includes_Awt
3103  |
3104  |  DESCRIPTION
3105  |    This function returns TRUE if the invoice contains withholding tax.
3106  |    It returns FALSE otherwise.
3107  |
3108  |  PARAMETERS
3109  |      X_Invoice_Id - Invoice Id
3110  |      X_Calling_Sequence - debug usage
3111  |
3112  |  KNOWN ISSUES:
3113  |
3114  |  NOTES:
3115  |
3116  |  MODIFICATION HISTORY
3117  |  Date         Author             Description of Change
3118  |  30-JUL-2003  SYIDNER            Creation
3119  |
3120  *============================================================================*/
3121 
3122   FUNCTION Invoice_Includes_Awt(
3123              P_Invoice_Id           IN NUMBER,
3124              P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN
3125 
3126   IS
3127     CURSOR Invoice_Validation IS
3128     SELECT i.invoice_id
3129       FROM ap_invoices_all i
3130      WHERE i.invoice_id = P_Invoice_Id
3131        AND EXISTS
3132            (SELECT il.invoice_id
3133               FROM ap_invoice_lines_all il
3134              WHERE il.invoice_id = i.invoice_id
3135                AND il.line_type_lookup_code = 'AWT'
3136                AND NVL(il.discarded_flag, 'N') <> 'Y'
3137                AND NVL(il.cancelled_flag, 'N') <> 'Y');
3138 
3139     l_invoice_id               ap_invoices_all.invoice_id%TYPE;
3140     current_calling_sequence   VARCHAR2(4000);
3141     debug_info                 VARCHAR2(240);
3142     l_return_var               BOOLEAN := FALSE;
3143 
3144   BEGIN
3145       current_calling_sequence := 'AP_INVOICES_UTILITY_PKG - Invoice_Includes_Awt';
3146 
3147       -------------------------------------------------------------
3148       debug_info := 'Invoice_Includes_Awt - Open cursor';
3149       -------------------------------------------------------------
3150       OPEN invoice_validation;
3151       FETCH invoice_validation INTO l_invoice_id;
3152       IF (invoice_validation%NOTFOUND) THEN
3153         CLOSE invoice_validation;
3154         l_invoice_id := null;
3155 
3156       END IF;
3157 
3158       IF ( invoice_validation%ISOPEN ) THEN
3159         CLOSE invoice_validation;
3160       END IF;
3161 
3162       IF (l_invoice_id IS NOT NULL) THEN
3163         l_return_var := TRUE;
3164 
3165       END IF;
3166 
3167    RETURN l_return_var;
3168 
3169   EXCEPTION
3170     WHEN OTHERS THEN
3171       if (SQLCODE <> -20001) then
3172         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
3173         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
3174         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
3175         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||P_Invoice_Id);
3176         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
3177       end if;
3178       debug_info := debug_info || 'Error occurred';
3179 
3180       IF ( invoice_validation%ISOPEN ) THEN
3181         CLOSE invoice_validation;
3182       END IF;
3183 
3184       APP_EXCEPTION.RAISE_EXCEPTION;
3185 
3186   END Invoice_Includes_Awt;
3187 
3188 /*=============================================================================
3189  |  FUNCTION - Inv_Matched_Finally_Closed_Po
3190  |
3191  |  DESCRIPTION
3192  |    This function returns TRUE if the invoice is matched to a finally closed
3193  |    PO.  It returns FALSE otherwise.
3194  |
3195  |  PARAMETERS
3196  |      X_Invoice_Id - Invoice Id
3197  |      X_Calling_Sequence - debug usage
3198  |
3199  |  KNOWN ISSUES:
3200  |
3201  |  NOTES:
3202  |
3203  |  MODIFICATION HISTORY
3204  |  Date         Author             Description of Change
3205  |  15-DEC-2003  SYIDNER            Creation
3206  |
3207  *============================================================================*/
3208   FUNCTION Inv_Matched_Finally_Closed_Po(
3209              P_Invoice_Id           IN NUMBER,
3210              P_Calling_sequence     IN VARCHAR2) RETURN BOOLEAN
3211 
3212   IS
3213     CURSOR Invoice_Validation IS
3214     SELECT i.invoice_id
3215       FROM ap_invoices_all i
3216      WHERE i.invoice_id = P_Invoice_Id
3217        AND EXISTS
3218            (SELECT ail.invoice_id
3219               FROM ap_invoice_lines_all ail,
3220                    po_line_locations_all pll
3221              WHERE ail.invoice_id = i.invoice_id
3222                AND ail.po_line_location_id = pll.line_location_id
3223                AND ail.org_id = pll.org_id
3224                AND pll.closed_code = 'FINALLY CLOSED');
3225 
3226     l_invoice_id               ap_invoices_all.invoice_id%TYPE;
3227     current_calling_sequence   VARCHAR2(4000);
3228     debug_info                 VARCHAR2(240);
3229     l_return_var               BOOLEAN := FALSE;
3230 
3231   BEGIN
3232     current_calling_sequence := 'AP_INVOICES_UTILITY_PKG - Inv_Matched_Finally_Closed_Po';
3233 
3234     ------------------------------------------------------------
3235     debug_info := 'Open cursor to verify if the invoice is '||
3236                   'matched to a finally closed PO';
3237     -------------------------------------------------------------
3238     OPEN invoice_validation;
3239     FETCH invoice_validation INTO l_invoice_id;
3240     IF (invoice_validation%NOTFOUND) THEN
3241       CLOSE invoice_validation;
3242       l_invoice_id := null;
3243 
3244     END IF;
3245 
3246     IF ( invoice_validation%ISOPEN ) THEN
3247       CLOSE invoice_validation;
3248     END IF;
3249 
3250     IF (l_invoice_id IS NOT NULL) THEN
3251       l_return_var := TRUE;
3252     END IF;
3253 
3254     RETURN l_return_var;
3255 
3256   EXCEPTION
3257     WHEN OTHERS THEN
3258       if (SQLCODE <> -20001) then
3259         FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
3260         FND_MESSAGE.SET_TOKEN('ERROR', SQLERRM);
3261         FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', current_calling_sequence);
3262         FND_MESSAGE.SET_TOKEN('PARAMETERS', 'Invoice Id = '||P_Invoice_Id);
3263         FND_MESSAGE.SET_TOKEN('DEBUG_INFO', debug_info);
3264       end if;
3265       debug_info := debug_info || 'Error occurred';
3266 
3267       IF ( invoice_validation%ISOPEN ) THEN
3268         CLOSE invoice_validation;
3269       END IF;
3270 
3271       APP_EXCEPTION.RAISE_EXCEPTION;
3272 
3273   END Inv_Matched_Finally_Closed_Po;
3274 
3275   --Invoice Lines: Distributions
3276   --Added the procedure to retrieve the max dist line number
3277   --for a particular invoice line.
3278   -----------------------------------------------------------------------
3279   -- Function get_max_dist_line_num returns the highest distribution line
3280   -- number of distributions belonging to invoice P_invoice_id for invoice line
3281   -- p_invoice_line_number.
3282   -----------------------------------------------------------------------
3283   FUNCTION get_max_dist_line_num (P_invoice_id IN number,
3284                                   P_invoice_line_number IN number) RETURN number
3285   IS
3286     l_max_dist_line_num NUMBER := 0;
3287   BEGIN
3288 
3289      select nvl(max(distribution_line_number),0)
3290      into   l_max_dist_line_num
3291      from   ap_invoice_distributions
3292      where  invoice_id = P_invoice_id
3293      and    invoice_line_number = P_invoice_line_number;
3294 
3295      return(l_max_dist_line_num);
3296 
3297   END get_max_dist_line_num;
3298 
3299 
3300  ---------------------------------------------------------------------
3301  --ETAX: Invwkb
3302  --This function when provided with a invoice_id, will return the
3303  --corresponding invoice_number.
3304  ---------------------------------------------------------------------
3305  FUNCTION get_invoice_num (P_Invoice_Id IN Number) RETURN VARCHAR2 IS
3306   l_invoice_num VARCHAR2(50) := NULL;
3307  BEGIN
3308 
3309    SELECT invoice_num
3310    INTO l_invoice_num
3311    FROM ap_invoices
3312    WHERE invoice_id = p_invoice_id;
3313 
3314    RETURN(l_invoice_num);
3315 
3316 
3317  EXCEPTION WHEN OTHERS THEN
3318    RETURN(NULL);
3319 
3320  END get_invoice_num;
3321 
3322 /*=============================================================================
3323  |  FUNCTION - get_retained_total
3324  |
3325  |  DESCRIPTION
3326  |      returns the total retained amount for the invoice.
3327  |
3328  |  KNOWN ISSUES:
3329  |
3330  |  NOTES:
3331  |
3332  |  MODIFICATION HISTORY
3333  |  Date         Author             Description of Change
3334  |
3335  *===========================================================================*/
3336 
3337     FUNCTION GET_RETAINED_TOTAL(P_Invoice_Id IN NUMBER, P_Org_Id IN NUMBER)
3338     RETURN NUMBER
3339     IS
3340       retained_total NUMBER := 0;
3341     BEGIN
3342 
3343        SELECT SUM(NVL(amount,0))
3344          INTO retained_total
3345          FROM ap_invoice_distributions_all aid
3346         WHERE aid.invoice_id = p_invoice_id
3347           AND aid.line_type_lookup_code = 'RETAINAGE'
3348           AND EXISTS
3349                   (SELECT 'X' FROM ap_invoice_lines_all ail
3350                     WHERE ail.invoice_id = p_invoice_id
3351                       AND ail.line_number = aid.invoice_line_number
3352                       AND ail.line_type_lookup_code <> 'RETAINAGE RELEASE');
3353 
3354         return (retained_total);
3355 
3356     END GET_RETAINED_TOTAL;
3357 
3358 /*=============================================================================
3359  |  FUNCTION -  get_item_total
3360  |
3361  |  DESCRIPTION
3362  |      returns the total item amount
3363  |
3364  |  KNOWN ISSUES:
3365  |
3366  |  NOTES:
3367  |
3368  |  MODIFICATION HISTORY
3369  |  Date         Author             Description of Change
3370  |
3371  *============================================================================*/
3372 
3373     FUNCTION Get_Item_Total(P_Invoice_Id IN NUMBER, P_Org_Id IN NUMBER)
3374 		    RETURN NUMBER IS
3375 
3376       item_total NUMBER := 0;
3377 
3378     BEGIN
3379 
3380       select sum(nvl(amount,0)) - sum(nvl(included_tax_amount,0))
3381       into   item_total
3382       from   ap_invoice_lines_all
3383       where  invoice_id = p_invoice_id
3384       and    line_type_lookup_code IN ('ITEM','RETAINAGE RELEASE');
3385 
3386       return(item_total);
3387 
3388     END Get_Item_Total;
3389 
3390 /*=============================================================================
3391  |  FUNCTION -  get_freight_total
3392  |
3393  |  DESCRIPTION
3394  |      returns the total item amount
3395  |
3396  |  KNOWN ISSUES:
3397  |
3398  |  NOTES:
3399  |
3400  |  MODIFICATION HISTORY
3401  |  Date         Author             Description of Change
3402  |
3403  *============================================================================*/
3404 
3405     FUNCTION Get_Freight_Total(P_Invoice_Id IN NUMBER, P_Org_Id IN NUMBER)
3406 		    RETURN NUMBER IS
3407 
3408       freight_total NUMBER := 0;
3409 
3410     BEGIN
3411 
3412       select sum(nvl(amount,0)) - sum(nvl(included_tax_amount,0))
3413       into   freight_total
3414       from   ap_invoice_lines_all
3415       where  invoice_id = p_invoice_id
3416       and    org_id     = p_org_id
3417       and    line_type_lookup_code = 'FREIGHT';
3418 
3419       return(freight_total);
3420 
3421     END Get_Freight_Total;
3422 
3423 
3424 /*=============================================================================
3425  |  FUNCTION -  get_misc_total
3426  |
3427  |  DESCRIPTION
3428  |      returns the total item amount
3429  |
3430  |  KNOWN ISSUES:
3431  |
3432  |  NOTES:
3433  |
3434  |  MODIFICATION HISTORY
3435  |  Date         Author             Description of Change
3436  |
3437  *============================================================================*/
3438 
3439     FUNCTION Get_Misc_Total(P_Invoice_Id IN NUMBER, P_Org_Id IN NUMBER)
3440 		    RETURN NUMBER IS
3441 
3442       misc_total NUMBER := 0;
3443 
3444     BEGIN
3445 
3446       select sum(nvl(amount,0)) - sum(nvl(included_tax_amount,0))
3447       into   misc_total
3448       from   ap_invoice_lines_all
3449       where  invoice_id = p_invoice_id
3450       and    org_id     = p_org_id
3451       and    line_type_lookup_code = 'MISCELLANEOUS';
3452 
3453       return(misc_total);
3454 
3455     END Get_Misc_Total;
3456 
3457 /*=============================================================================
3458  |  FUNCTION -  get_prepay_app_total
3459  |
3460  |  DESCRIPTION
3461  |      returns the total prepayments applied including recoupments
3462  |
3463  |  KNOWN ISSUES:
3464  |
3465  |  NOTES:
3466  |
3467  |  MODIFICATION HISTORY
3468  |  Date         Author             Description of Change
3469  |
3470  *============================================================================*/
3471 
3472     FUNCTION Get_Prepay_App_Total(P_Invoice_Id IN NUMBER, P_Org_Id IN NUMBER)
3473 		    RETURN NUMBER IS
3474 
3475       prepay_app_total NUMBER := 0;
3476 
3477     BEGIN
3478 
3479       select sum(nvl(amount,0))
3480       into   prepay_app_total
3481       from   ap_invoice_distributions_all
3482       where  invoice_id = p_invoice_id
3483       and    org_id     = p_org_id
3484       and    line_type_lookup_code = 'PREPAY';
3485 
3486       return(prepay_app_total);
3487 
3488     END Get_Prepay_App_Total;
3489 
3490 /*=============================================================================
3491  |  FUNCTION - get_invoice_status
3492  |
3493  |  DESCRIPTION
3494  |      returns the invoice status lookup code.
3495  |
3496  |  KNOWN ISSUES:
3497  |
3498  |  NOTES
3499  |      ISP Invoice Statuses
3500  |                   IN_PROCESS
3501  |                   UNSUBMITTED
3502  |                   IN_NEGOTIATION
3503  |                   CANCELLED
3504  |
3505  |
3506  |  MODIFICATION HISTORY
3507  |  Date         Author             Description of Change
3508  |
3509  *============================================================================*/
3510  -- Bug 5345946 XBuild7 Code Cleanup
3511     FUNCTION get_invoice_status(
3512                  p_invoice_id               IN NUMBER,
3513                  p_invoice_amount           IN NUMBER,
3514                  p_payment_status_flag      IN VARCHAR2,
3515                  p_invoice_type_lookup_code IN VARCHAR2)
3516     RETURN VARCHAR2 IS
3517 
3518       l_invoice_status       		VARCHAR2(25);
3519       l_approval_ready_flag        	VARCHAR2(1);
3520       l_cancelled_date 			    DATE;
3521       l_negotiate_lines_count		NUMBER;
3522       l_invoice_source			    VARCHAR2(25);
3523       l_invoice_type_lookup_code    VARCHAR2(30);
3524 
3525     BEGIN
3526       --
3527       SELECT ai.cancelled_date,
3528              ai.approval_ready_flag,
3529              ai.invoice_type_lookup_code,
3530              ai.source
3531       INTO   l_cancelled_date,
3532              l_approval_ready_flag,
3533              l_invoice_type_lookup_code,
3534              l_invoice_source
3535       FROM   ap_invoices_all ai
3536       WHERE  ai.invoice_id = p_invoice_id
3537         AND  ai.source = 'ISP';
3538 
3539       -- If cancelled date is not null, return 'CANCELLED'
3540       --
3541       IF ( l_cancelled_date IS NOT NULL) THEN
3542         RETURN('CANCELLED');
3543       END IF;
3544 
3545       -- If invoice is saved for later in ISP, return 'UNSUBMITTED'.
3546       -- Temporarily approval_ready_flag = 'S' in ap_invoices_all  handles the
3547       -- the unsubmitted invoices.
3548       IF ( l_approval_ready_flag = 'S' ) THEN
3549         RETURN('UNSUBMITTED');
3550       END IF;
3551 
3552 
3553       -- If invoice is in negotiation, return 'IN_NEGOTIATION'.
3554       --
3555       IF ( l_approval_ready_flag <> 'S' ) THEN
3556 
3557          IF (l_invoice_type_lookup_code = 'INVOICE REQUEST') THEN
3558 
3559 		      SELECT count(*)
3560 		      INTO   l_negotiate_lines_count
3561 		      FROM   ap_apinv_approvers
3562 		      WHERE  invoice_id = p_invoice_id
3563 		      AND    approval_status = 'NEGOTIATE'
3564 		      AND rownum =1;
3565 
3566 		      IF ( l_negotiate_lines_count > 0 ) THEN
3567 		        RETURN('IN_NEGOTIATION');
3568 		      END IF;
3569 
3570 	      ELSE  --- Standard, Credit-Memo or Prepayments
3571 
3572 		      SELECT count(*)
3573 		      INTO   l_negotiate_lines_count
3574 		      FROM   ap_holds_all
3575 		      WHERE  invoice_id = p_invoice_id
3576 		      AND    wf_status = 'NEGOTIATE'
3577 		      AND rownum =1;
3578 
3579 		      IF ( l_negotiate_lines_count > 0 ) THEN
3580 		        RETURN('IN_NEGOTIATION');
3581 		      END IF;
3582 
3583 	      END IF;
3584 	      --
3585 	   END IF;
3586 	   --
3587 	   RETURN('IN_PROCESS');
3588        --
3589     END get_invoice_status;
3590 
3591     PROCEDURE get_bank_details(
3592 	p_invoice_currency_code	IN VARCHAR2,
3593 	p_party_id				IN NUMBER,
3594 	p_party_site_id			IN NUMBER,
3595 	p_supplier_site_id			IN NUMBER,
3596 	p_org_id				IN NUMBER,
3597 	x_bank_account_name		OUT NOCOPY VARCHAR2,
3598 	x_bank_account_id		OUT NOCOPY VARCHAR2,
3599 	x_bank_account_number	OUT NOCOPY VARCHAR2) IS
3600 
3601 	cursor c_get_bank_details is
3602 		select  bank_account_name,
3603 			bank_account_id,
3604 			bank_account_number
3605 		from (
3606 		SELECT  b.bank_account_name,
3607 			b.ext_bank_account_id bank_account_id,
3608 			b.bank_account_number,
3609 			rank() over (partition by ibyu.instrument_id, ibyu.instrument_type order by ibyu.instrument_payment_use_id) not_dup
3610 		  FROM  IBY_PMT_INSTR_USES_ALL ibyu,
3611 			IBY_EXT_BANK_ACCOUNTS_V b,
3612 			IBY_EXTERNAL_PAYEES_ALL ibypayee
3613 		 WHERE ibyu.instrument_id = b.ext_bank_account_id
3614 		   AND ibyu.instrument_type = 'BANKACCOUNT'
3615 		   AND (b.currency_code = p_invoice_currency_code OR b.currency_code is null
3616 			OR NVL(b.foreign_payment_use_flag,'N')='Y')
3617 		   AND ibyu.ext_pmt_party_id = ibypayee.ext_payee_id
3618 		   AND ibyu.payment_flow = 'DISBURSEMENTS'
3619 		   AND ibypayee.payment_function = 'PAYABLES_DISB'
3620 		   AND ibypayee.payee_party_id = p_party_id
3621 		   AND trunc(sysdate) between trunc(NVL(ibyu.start_date,sysdate-1)) AND trunc(NVL(ibyu.end_date,sysdate+1))
3622 		   AND trunc(sysdate) between trunc(NVL(b.start_date,sysdate-1)) AND trunc(NVL(b.end_date,sysdate+1))
3623 		   AND (ibypayee.party_site_id is null OR ibypayee.party_site_id = p_party_site_id)
3624 		   AND (ibypayee.supplier_site_id is null OR ibypayee.supplier_site_id = p_supplier_site_id)
3625 		   AND (ibypayee.org_id is null OR
3626 			(ibypayee.org_id = p_org_id AND ibypayee.org_type = 'OPERATING_UNIT')))
3627 		where not_dup=1;
3628 
3629     BEGIN
3630 
3631 	OPEN c_get_bank_details;
3632 	FETCH c_get_bank_details INTO x_bank_account_name, x_bank_account_id, x_bank_account_number;
3633 	CLOSE c_get_bank_details;
3634 
3635     EXCEPTION
3636 	WHEN OTHERS THEN
3637 		x_bank_account_name		:= NULL;
3638 		x_bank_account_id		:= NULL;
3639 		x_bank_account_number	:= NULL;
3640     END get_bank_details;
3641 
3642 END AP_INVOICES_UTILITY_PKG;
3643