DBA Data[Home] [Help]

PACKAGE BODY: APPS.AP_IMPORT_VALIDATION_PKG

Source


1 PACKAGE BODY AP_IMPORT_VALIDATION_PKG AS
2 /* $Header: apiimvtb.pls 120.121.12010000.27 2009/02/19 11:14:21 ctetala ship $ */
3 
4 ------------------------------------------------------------------------
5 -- This function is used to perform invoice header level validations.
6 --
7 ------------------------------------------------------------------------
8 
9 FUNCTION v_check_invoice_validation(
10            p_invoice_rec                 IN OUT NOCOPY
11              AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
12            p_match_mode                     OUT NOCOPY VARCHAR2,
13            p_min_acct_unit_inv_curr         OUT NOCOPY NUMBER,
14            p_precision_inv_curr             OUT NOCOPY NUMBER,
15 	   p_positive_price_tolerance      OUT NOCOPY      NUMBER,
16 	   p_negative_price_tolerance      OUT NOCOPY      NUMBER,
17 	   p_qty_tolerance                 OUT NOCOPY      NUMBER,
18 	   p_qty_rec_tolerance             OUT NOCOPY      NUMBER,
19 	   p_max_qty_ord_tolerance         OUT NOCOPY      NUMBER,
20 	   p_max_qty_rec_tolerance         OUT NOCOPY      NUMBER,
21 	   p_amt_tolerance		   OUT NOCOPY      NUMBER,
22 	   p_amt_rec_tolerance		   OUT NOCOPY	   NUMBER,
23 	   p_max_amt_ord_tolerance         OUT NOCOPY      NUMBER,
24 	   p_max_amt_rec_tolerance         OUT NOCOPY      NUMBER,
25 	   p_goods_ship_amt_tolerance      OUT NOCOPY      NUMBER,
26 	   p_goods_rate_amt_tolerance      OUT NOCOPY      NUMBER,
27 	   p_goods_total_amt_tolerance     OUT NOCOPY      NUMBER,
28 	   p_services_ship_amt_tolerance   OUT NOCOPY      NUMBER,
29 	   p_services_rate_amt_tolerance   OUT NOCOPY      NUMBER,
30 	   p_services_total_amt_tolerance  OUT NOCOPY      NUMBER,
31            p_base_currency_code          IN            VARCHAR2,
32            p_multi_currency_flag         IN            VARCHAR2,
33            p_set_of_books_id             IN            NUMBER,
34            p_default_exchange_rate_type  IN            VARCHAR2,
35            p_make_rate_mandatory_flag    IN            VARCHAR2,
36            p_default_last_updated_by     IN            NUMBER,
37            p_default_last_update_login   IN            NUMBER,
38            p_fatal_error_flag            OUT NOCOPY    VARCHAR2,
39            p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
40            p_calc_user_xrate             IN            VARCHAR2,
41            p_prepay_period_name          IN OUT NOCOPY VARCHAR2,
42 	   p_prepay_invoice_id		 OUT NOCOPY    NUMBER,
43 	   p_prepay_case_name		 OUT NOCOPY    VARCHAR2,
44            p_request_id                  IN            NUMBER,
45 	   p_allow_interest_invoices     IN	       VARCHAR2, --Bug4113223
46            p_calling_sequence            IN            VARCHAR2)
47 RETURN BOOLEAN IS
48 
49   check_inv_validation_failure  EXCEPTION;
50   import_invoice_failure	EXCEPTION;
51 
52   l_current_invoice_status      VARCHAR2(1) := 'Y';
53   l_vendor_id                   PO_VENDORS.VENDOR_ID%TYPE;
54   l_vendor_site_id              PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
55   l_vendor_site_id_per_po       PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
56   l_invoice_num                 AP_INVOICES.INVOICE_NUM%TYPE;
57   l_inv_currency_code           AP_INVOICES.INVOICE_CURRENCY_CODE%TYPE;
58   l_exchange_rate               AP_INVOICES.EXCHANGE_RATE%TYPE;
59   l_exchange_date               AP_INVOICES.EXCHANGE_DATE%TYPE;
60   l_invoice_type_lookup_code    AP_INVOICES.INVOICE_TYPE_LOOKUP_CODE%TYPE;
61   l_awt_group_id                AP_INVOICES.AWT_GROUP_ID%TYPE;
62   l_pay_awt_group_id            AP_INVOICES.PAY_AWT_GROUP_ID%TYPE;--bug6639866
63   l_terms_id                    AP_INVOICES.TERMS_ID%TYPE;
64   l_terms_date                  AP_INVOICES.TERMS_DATE%TYPE;
65   l_pay_currency_code           AP_INVOICES.PAYMENT_CURRENCY_CODE%TYPE;
66   l_pay_cross_rate_date         AP_INVOICES.PAYMENT_CROSS_RATE_DATE%TYPE;
67   l_pay_cross_rate              AP_INVOICES.PAYMENT_CROSS_RATE%TYPE;
68   l_pay_cross_rate_type         AP_INVOICES.PAYMENT_CROSS_RATE_TYPE%TYPE;
69   l_invoice_base_amount         AP_INVOICES.BASE_AMOUNT%TYPE;
70   l_temp_invoice_status         VARCHAR2(1) := 'Y';
71   l_po_exists_flag              VARCHAR2(1) := 'N';
72   current_calling_sequence      VARCHAR2(2000);
73   debug_info                    VARCHAR2(500);
74   l_terms_date_basis            VARCHAR2(25);
75   l_primary_paysite_id          PO_VENDOR_SITES.VENDOR_SITE_ID%TYPE;
76   --For bug 2713327 Added temporary variable to hold the value of
77   --vendor_id in the interface table
78   l_temp_vendor_id                NUMBER(15) := p_invoice_rec.vendor_id;
79   --Bug 4051803
80   l_positive_price_tolerance      NUMBER;
81   l_negative_price_tolerance      NUMBER;
82   l_qty_tolerance                 NUMBER;
83   l_qty_rec_tolerance             NUMBER;
84   l_max_qty_ord_tolerance         NUMBER;
85   l_max_qty_rec_tolerance         NUMBER;
86   l_max_amt_ord_tolerance         NUMBER;
87   l_max_amt_rec_tolerance         NUMBER;
88   l_ship_amt_tolerance            NUMBER;
89   l_rate_amt_tolerance            NUMBER;
90   l_total_amt_tolerance           NUMBER;
91 
92   l_party_site_id                 NUMBER(15);
93 
94 BEGIN
95 
96   -- Update the calling sequence
97   current_calling_sequence :=
98              'AP_IMPORT_VALIDATION_PKG.v_check_invoice_validation<-'
99              ||P_calling_sequence;
100 
101   --------------------------------------------------------------------------
102   -- Step 0a
103   -- Initialize invoice_date if null
104   --------------------------------------------------------------------------
105   debug_info := '(Check Invoice Validation 0) Initialize invoice_date if null';
106   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
107     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
108                                   debug_info);
109   END IF;
110 
111   IF (p_invoice_rec.invoice_date IS NULL) THEN
112     p_invoice_rec.invoice_date := trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
113   END IF;
114 
115   --------------------------------------------------------------------------
116   -- Step 1
117   -- Check for Invalid or Inactive PO
118   --------------------------------------------------------------------------
119   debug_info :=
120      '(Check Invoice Validation 1) Check for Invalid and Inactive PO';
121   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
122     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
123                                   debug_info);
124   END IF;
125   --
126   IF (p_invoice_rec.po_number IS NOT NULL) THEN
127     -- IF PO Number is given , we should not check for Supplier Number
128     -- or Supplier Site.  PO Number can also be used for this check, but a
129     -- flag is set for this purpose.
130     l_po_exists_flag := 'Y';
131 
132     IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_po (
133           p_invoice_rec,                                  -- IN
134           p_default_last_updated_by,                      -- IN
135           p_default_last_update_login,                    -- IN
136           l_temp_invoice_status,                          -- OUT
137           p_po_vendor_id      => l_vendor_id,             -- OUT
138           p_po_vendor_site_id => l_vendor_site_id_per_po, -- OUT
139           p_po_exists_flag    => l_po_exists_flag,        -- OUT
140           p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
141       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
142         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
143                      'v_check_invalid_po<-'||current_calling_sequence);
144       END IF;
145       RAISE check_inv_validation_failure;
146     END IF;
147 
148     -- We need to set the current status to 'N' only if the temp invoice status
149     -- returns 'N'. So all temp returns of 'N' will overwrite the current
150     -- invoice status to 'N' which finally would be returned to the calling
151     -- function.
152     IF (l_temp_invoice_status = 'N') THEN
153       l_current_invoice_status := l_temp_invoice_status;
154     END IF;
155 
156     --
157     -- show output values (only if debug_switch = 'Y')
158     --
159     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
160       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
161                 '------------------>
162                 l_temp_invoice_status   = '||l_temp_invoice_status
163             ||' l_vendor_id             = '||to_char(l_vendor_id)
164             ||' l_vendor_site_id_per_po = '||to_char(l_vendor_site_id_per_po)
165             ||' l_po_exists_flag        = '||l_po_exists_flag);
166     END IF;
167 
168     -- It is possible to create a PO for a Supplier / Supplier Site
169     -- that has been end dated or in some other way invalidated
170     -- before running  the import.  If the PO exists it is assumed
171     -- that the Supplier /  Supplier Site is valid.  This allows an
172     -- invoice to be created for an invalid Supplier / Supplier Site.
173     -- We no longer check the PO flag before validating the Supplier
174     -- info.  Also since we are no longer assuming a correct Supplier
175     -- if the PO exists, we have to get the  vendor_id from the PO if
176     -- it is not in the Interface table row.
177     IF (p_invoice_rec.vendor_id IS NULL AND l_po_exists_flag = 'Y') then
178       p_invoice_rec.vendor_id := l_vendor_id;
179     END IF;
180 
181   END IF; -- p_invoice_rec.po_number is not null
182 
183   ---------------------------------------------------------------------------
184   -- Step 2
185   -- Check for Invalid or Inconsistent Legal Entity Name and Id
186   ---------------------------------------------------------------------------
187   debug_info := '(Check Invoice Validation 2) Check for Invalid Legal Entity';
188   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
189     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
190                                   debug_info);
191   END IF;
192 
193 -- YIDSAL.  Include here call the validate function for the LE Id and NaMe
194 --  Surekha will give us the API name.
195 
196   ---------------------------------------------------------------------------
197   -- Step 3
198   -- Check for Invalid Supplier or Inconsistent Supplier
199   ---------------------------------------------------------------------------
200   debug_info := '(Check Invoice Validation 2) Check for Invalid Supplier';
201   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
202     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
203                                   debug_info);
204   END IF;
205 
206   -- Added party validation for payment request project
207   IF p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST' THEN
208 
209      IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_party (
210         p_invoice_rec,                                       -- IN
211         p_default_last_updated_by,                           -- IN
212         p_default_last_update_login,                         -- IN
213         p_current_invoice_status => l_temp_invoice_status,   -- IN OUT
214         p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
215         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
216           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
217             'v_check_invalid_party <-'||current_calling_sequence);
218         END IF;
219         RAISE check_inv_validation_failure;
220       END IF;
221 
222   ELSE
223 
224       IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier (
225             p_invoice_rec,                                       -- IN
226             p_default_last_updated_by,                           -- IN
227             p_default_last_update_login,                         -- IN
228             p_return_vendor_id       => l_vendor_id,             -- OUT
229             p_current_invoice_status => l_temp_invoice_status,   -- IN OUT
230             p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
231         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
232           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
233             'v_check_invalid_supplier<-'||current_calling_sequence);
234         END IF;
235         RAISE check_inv_validation_failure;
236       END IF;
237 
238       IF p_invoice_rec.vendor_id IS NULL  THEN
239          p_invoice_rec.vendor_id := l_vendor_id;
240 
241       END IF;
242 
243   END IF;
244 
245  --For bug 2713327 changed p_invoice_rec.vendor_id to l_temp_vendor_id
246  --At this point the value of p_invoice_rec.vendor_id will not be NULL as
247  --it would have been retrieved from PO if one exists or it would have been keyed in.
248  --So the value of vendor id in interface table should be updated with correct value
249  --for retrieving the output as it is checking for ii.vendor_id=i.vendor_id in
250  --the query Q_AUDIT
251 
252  --added nvl for bug 7314487
253   IF l_temp_vendor_id is NULL
254               AND nvl(p_invoice_rec.invoice_type_lookup_code,'STANDARD') <> 'PAYMENT REQUEST'
255   THEN UPDATE ap_invoices_interface
256        SET vendor_id = l_vendor_id
257        WHERE invoice_id = p_invoice_rec.invoice_id;
258   END IF;
259 
260   IF (l_temp_invoice_status = 'N') THEN
261     l_current_invoice_status := l_temp_invoice_status;
262   END IF;
263 
264   debug_info := '(Check Invoice Validation 2) Validated Supplier';
265   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
266     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
267                                   debug_info);
268   END IF;
269   --
270   -- show output values (only if debug_switch = 'Y')
271   --
272   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
273     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
274           '------------------>
275             l_temp_invoice_status  = '||l_temp_invoice_status
276         ||' l_vendor_id             = '||to_char(l_vendor_id));
277   END IF;
278 
279   IF (p_invoice_rec.vendor_id is NOT NULL)
280            OR (p_invoice_rec.party_id IS NOT NULL) THEN
281 
282     -------------------------------------------------------------------------
283     -- Step 4
284     -- Check for Invalid Supplier Site only if there is a valid Supplier
285     -- Also, populate vendor_site_id if all the following
286     -- conditions are met:
287     -- 1) vendor_site_id is null
288     -- 2) vendor_site_id could be derived in the find primary paysite function
289     --    or the vendor site check function
290     -- 3) if either the find primary paysite succeded or the vendor site
291     --    check function returned that the invoice is valid
292     --    as far as vendor site is concerned.
293     -------------------------------------------------------------------------
294     debug_info := '(Check Invoice Validation 3) '||
295                    'Check for Invalid Supplier Site, if Supplier is valid';
296     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
297       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
298                                     debug_info);
299     END IF;
300 
301 
302     -- Payment Request: Added Payment Request invoice type to the IF condition
303 
304     -- Check for invalid supplier site.  If an invalid supplier site exists,
305     -- or inconsistent data exists, this is a fatal error.
306     -- Do not perform further validation.  If a valid vendor site exists,
307     -- the function will return the value of the vendor site.
308     IF ((p_invoice_rec.vendor_site_id is null) and
309         (p_invoice_rec.vendor_site_code is null) and
310         (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')) Then
311 
312       debug_info := '(Check Invoice Validation 3.1) Supplier Site is per PO';
313       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
314         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
315                                       debug_info);
316       END IF;
317 
318       IF (AP_IMPORT_UTILITIES_PKG.find_vendor_primary_paysite(
319             p_vendor_id                  => p_invoice_rec.vendor_id, -- IN
320             p_vendor_primary_paysite_id  => l_primary_paysite_id,    -- OUT
321             p_calling_sequence           => current_calling_sequence)
322             <> true ) THEN
323         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
324           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
325             'find_vendor_primary_paysite<-'||current_calling_sequence);
326         END IF;
327         RAISE check_inv_validation_failure;
328       END IF;
329 
330       IF (l_primary_paysite_id is NOT NULL ) THEN
331         p_invoice_rec.vendor_site_id := l_primary_paysite_id;
332       ELSE
333         p_invoice_rec.vendor_site_id := l_vendor_site_id_per_po;
334       END IF;
335 
336     ELSE
337       debug_info := '(Check Invoice Validation 3.2) Supplier Site is per EDI';
338       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
339         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
340           debug_info);
341       END IF;
342 
343     END IF;
344 
345 
346     --Payment Request: Added IF condition for Payment Request
347     IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST'
348         /*Bug 8247859*/OR (p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT'
349             AND p_invoice_rec.party_site_id is NOT NULL)/*Bug 8247859*/) THEN
350        IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_party_site (
351               p_invoice_rec,                                       -- IN
352               p_default_last_updated_by,                           -- IN
353               p_default_last_update_login,                         -- IN
354               p_return_party_site_id    => l_party_site_id,        -- OUT
355               p_terms_date_basis        => l_terms_date_basis,     -- OUT
356               p_current_invoice_status  => l_temp_invoice_status,  -- IN OUT
357               p_calling_sequence => current_calling_sequence) <> TRUE ) THEN
358           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
359             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
360                                   'v_check_invalid_party_site<-'
361                                   ||current_calling_sequence);
362           END IF;
363           RAISE check_inv_validation_failure;
364        END IF;
365 
366     ELSE
367 
368        IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier_site (
369               p_invoice_rec,                                       -- IN
370               l_vendor_site_id_per_po,                             -- IN
371               p_default_last_updated_by,                           -- IN
372               p_default_last_update_login,                         -- IN
373               p_return_vendor_site_id   => l_vendor_site_id,       -- OUT
374               p_terms_date_basis        => l_terms_date_basis,     -- OUT
375               p_current_invoice_status  => l_temp_invoice_status,  -- IN OUT
376                 p_calling_sequence => current_calling_sequence) <> TRUE ) THEN
377           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
378             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
379                                       'v_check_invalid_supplier_site<-'
380                                       ||current_calling_sequence);
381           END IF;
382           RAISE check_inv_validation_failure;
383        END IF;
384 
385     END IF;
386 
387     IF (l_temp_invoice_status = 'N') THEN
388       l_current_invoice_status := l_temp_invoice_status;
389     ELSE
390       --Bug 6711062
391       IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST'
392           /*Bug 8247859*/OR (p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT'
393             AND p_invoice_rec.party_site_id is NOT NULL)/*Bug 8247859*/)  THEN
394          p_invoice_rec.party_site_id := l_party_site_id;
395       ELSE
396          p_invoice_rec.vendor_site_id := l_vendor_site_id;
397          p_invoice_rec.party_site_id := l_party_site_id;
398       END IF;
399     END IF;
400 
401     debug_info := '(Check Invoice Validation 3) Validated Supplier Site';
402     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
403       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
404                                     debug_info);
405     END IF;
406 
407     --
408     -- show output values (only if debug_switch = 'Y')
409     --
410     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
411       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
412             '------------------>
413             l_temp_invoice_status        = '||l_temp_invoice_status
414         ||' l_vendor_site_id         = '||to_char(l_vendor_site_id)
415         ||' l_party_site_id          = '||to_char(l_party_site_id));
416 
417     END IF;
418 
419 
420 
421     --we should make sure the party and supplier info is consistent as well as
422     --populate the id's that may be missing
423 
424     if(AP_IMPORT_VALIDATION_PKG.v_check_party_vendor(
425         p_invoice_rec,
426         l_temp_invoice_status,
427         current_calling_sequence,
428         p_default_last_updated_by,
429         p_default_last_update_login) <> TRUE) then
430       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
431               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
432                                         'v_check_party_vendor<-'
433                                         ||current_calling_sequence);
434       END IF;
435       RAISE check_inv_validation_failure;
436     END IF;
437 
438     IF (l_temp_invoice_status = 'N') THEN
439       l_current_invoice_status := l_temp_invoice_status;
440     END IF;
441 
442     debug_info := '(Check Invoice Validation 3.5) Validated party and vendor info ' ||
443                   'l_temp_invoice_status = '||l_temp_invoice_status;
444     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
445       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
446                                     debug_info);
447     END IF;
448 
449 
450 
451     --Bug:4051803
452     --Contract Payments: Tolerances Redesign, added the max_amt_ord and max_amt_rec
453     --tolerances.
454     IF (p_invoice_rec.vendor_site_id IS NOT NULL AND
455           p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST') THEN
456        IF ( ap_import_utilities_pkg.get_tolerance_info(
457        		p_invoice_rec.vendor_site_id,   -- IN
458 		p_positive_price_tolerance,     -- OUT
459 		p_negative_price_tolerance,     -- OUT
460 	        p_qty_tolerance,                -- OUT
461 	        p_qty_rec_tolerance,            -- OUT
462 	        p_max_qty_ord_tolerance,        -- OUT
463 	        p_max_qty_rec_tolerance,        -- OUT
464 		p_amt_tolerance,		-- OUT
465 		p_amt_rec_tolerance,		-- OUT
466 		p_max_amt_ord_tolerance,        -- OUT
467 	        p_max_amt_rec_tolerance,        -- OUT
468 	        p_goods_ship_amt_tolerance,     -- OUT
469 	        p_goods_rate_amt_tolerance,     -- OUT
470 	        p_goods_total_amt_tolerance,    -- OUT
471 		p_services_ship_amt_tolerance,  -- OUT
472 	        p_services_rate_amt_tolerance,  -- OUT
473 	        p_services_total_amt_tolerance, -- OUT
474 	        current_calling_sequence
475 	        ) <> TRUE) THEN
476 
477              if AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' then
478                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, 'get_tolerance_info()<-'||
479 	                     current_calling_sequence);
480              end if;
481              RAISE import_invoice_failure;
482         END IF;
483     END IF;
484 
485 
486     IF ((p_invoice_rec.vendor_site_id is NOT NULL)
487             OR (p_invoice_rec.party_site_id IS NOT NULL)) THEN
488 
489       -----------------------------------------------------------------------
490       -- Step 5
491       -- Check for invoice number already in use within either
492       -- the permanent tables or interface tables.  If the invoice
493       -- number is already in use, this is a fatal error.  Do not
494       -- perform further validation checking.
495       -- Check performed only if there is a valid Supplier and Supplier Site
496       -----------------------------------------------------------------------
497       debug_info := '(Check Invoice Validation 4) '||
498                      'Check for Invalid Invoice Number '||
499                      ',if Supplier Site is valid';
500       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
501         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
502                                       debug_info);
503       END IF;
504 
505       IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_invoice_num (
506             p_invoice_rec,                                           -- IN
507 	    --bug4113223
508 	    p_allow_interest_invoices,				     -- IN
509             l_invoice_num,                                           -- OUT
510             p_default_last_updated_by,                               -- IN
511             p_default_last_update_login,                             -- IN
512             p_current_invoice_status     => l_temp_invoice_status,   -- IN OUT
513             p_calling_sequence           => current_calling_sequence)
514             <> TRUE ) THEN
515         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
516           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
517             'v_check_invalid_invoice_num<- '||current_calling_sequence);
518         END IF;
519         RAISE check_inv_validation_failure;
520       END IF;
521 
522       IF (l_temp_invoice_status = 'N') THEN
523         l_current_invoice_status := l_temp_invoice_status;
524       ELSE
525         IF (p_invoice_rec.invoice_num is NULL AND
526         l_invoice_num is not NULL) THEN
527           p_invoice_rec.invoice_num := l_invoice_num;
528         END IF;
529       END IF;
530 
531       --
532       -- show output values (only if debug_switch = 'Y')
533       --
534       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
535         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
536         '------------------> l_temp_invoice_status  = '||l_temp_invoice_status);
537       END IF;
538 
539       -- only continue if a valid invoice number was found
540       IF l_current_invoice_status = 'Y' THEN
541 
542         -----------------------------------------------------------------------
543         -- Step 6
544         -- Check for Invalid Currency Code only if there is a valid Invoice No
545         -- Also, populate currency code if all the following
546         -- conditions are met:
547         -- 1) invoice_currency_code is null
548         -- 2) invoice_currency_code could be derived in the inv curr
549         --    check function
550         -- 3) the inv curr check function returned that the invoice is valid
551         --    as far as inv currency code is concerned.
552         -----------------------------------------------------------------------
553         debug_info := '(Check Invoice Validation 5) Check for Currency Code ,'
554                       ||'if Invoice No. is valid';
555         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
556           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
557                                         debug_info);
558         END IF;
559 
560         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_inv_curr_code (
561             p_invoice_rec,                                             -- IN
562             p_inv_currency_code      => l_inv_currency_code,           -- OUT
563             p_min_acc_unit_inv_curr  => p_min_acct_unit_inv_curr,      -- OUT
564             p_precision_inv_curr     => p_precision_inv_curr,          -- OUT
565             p_default_last_updated_by => p_default_last_updated_by,    -- IN
566             p_default_last_update_login => p_default_last_update_login,-- IN
567             p_current_invoice_status => l_temp_invoice_status,         -- IN OUT
568             p_calling_sequence       => current_calling_sequence)
569               <> TRUE ) THEN
570           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
571             AP_IMPORT_UTILITIES_PKG.Print(
572               AP_IMPORT_INVOICES_PKG.g_debug_switch,
573               'v_check_invalid_currency_code<-'||current_calling_sequence);
574           END IF;
575           RAISE check_inv_validation_failure;
576         END IF;
577 
578         IF (l_temp_invoice_status = 'N') THEN
579           l_current_invoice_status := l_temp_invoice_status;
580         ELSE
581           IF (p_invoice_rec.invoice_currency_code is NULL AND
582               l_inv_currency_code is not NULL) THEN
583             p_invoice_rec.invoice_currency_code := l_inv_currency_code;
584           END IF;
585         END IF;
586         --
587 
588         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
589           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
590             '--------------> l_temp_invoice_status  = ' ||l_temp_invoice_status
591             ||' l_inv_currency_code = '|| l_inv_currency_code);
592         END IF;
593 
594         ----------------------------------------------------------------------
595         -- Step 7
596         -- Check for Invalid Invoice Lookup Code and Amt.
597         -- only if there is a valid Invoice No.
598         -- Also, populate invoice type lookup code if all the following
599         -- conditions are met:
600         -- 1) invoice_type_lookup_code is null null
601         -- 2) invoice_type lookup_code could be derived in the invoice type
602         --    check function and
603         -- 3) the invoice type check function returned that the invoice is
604         --    valid as far as invoice type/amount information is concerned.
605         ----------------------------------------------------------------------
606         debug_info := '(Check Invoice Validation 6) Check for Invoice Lookup '
607                       ||'Code and Amount ,if Invoice No. is valid';
608         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
609           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
610                                         debug_info);
611         END IF;
612 
613         IF (AP_IMPORT_VALIDATION_PKG.v_check_invoice_type_amount (
614               p_invoice_rec,                                          -- IN
615               l_invoice_type_lookup_code,                             -- OUT
616               p_match_mode,                                           -- OUT
617               p_precision_inv_curr,                                   -- IN
618               p_default_last_updated_by,                              -- IN
619               p_default_last_update_login,                            -- IN
620               p_current_invoice_status     => l_temp_invoice_status,  -- IN OUT
621               p_calling_sequence           => current_calling_sequence)
622               <> TRUE ) THEN
623           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
624             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
625               'v_check_invoice_type_amount<-'||current_calling_sequence);
626           END IF;
627           RAISE check_inv_validation_failure;
628         END IF;
629 
630         IF (l_temp_invoice_status = 'N') THEN
631           l_current_invoice_status := l_temp_invoice_status;
632         ELSE
633           IF (p_invoice_rec.invoice_type_lookup_code is NULL AND
634               l_invoice_type_lookup_code is not NULL) THEN
635             p_invoice_rec.invoice_type_lookup_code :=
636                                 l_invoice_type_lookup_code;
637           END IF;
638         END IF;
639 
640         --
641         -- show output values (only if debug_switch = 'Y')
642         --
643         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
644           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
645             '------------------>
646             l_temp_invoice_status  = '||l_temp_invoice_status
647             ||' p_match_mode = '||p_match_mode);
648         END IF;
649 
650         ----------------------------------------------------------------------
651         -- Step 8
652         -- Check for Invalid AWT Group only if there is a valid Invoice No.
653         -- Also, populate awt_group_id if all the following conditions are met:
654         -- 1) awt_group_id is null
655         -- 2) awt_group_id could be derived in the awt group check function
656         -- 3) the awt group check function returned that the invoice is valid
657         --    as far as awt group information is concerned.
658         ----------------------------------------------------------------------
659         debug_info := '(Check Invoice Validation 7) Check for AWT Group ,'
660                        ||'if Invoice No. is valid';
661         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
662           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
663                                         debug_info);
664         END IF;
665 
666         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_awt_group(
667            p_invoice_rec,                                             -- IN
668            p_awt_group_id              => l_awt_group_id,             -- OUT
669            p_default_last_updated_by   => p_default_last_updated_by,  -- IN
670            p_default_last_update_login => p_default_last_update_login,-- IN
671            p_current_invoice_status  => l_temp_invoice_status,      -- IN OUT
672            p_calling_sequence        => current_calling_sequence)
673               <> TRUE ) THEN
674           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
675             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
676               'v_check_invalid_awt_group<-'||current_calling_sequence);
677           END IF;
678           RAISE check_inv_validation_failure;
679         END IF;
680 
681         --
682         IF (l_temp_invoice_status = 'N') THEN
683           l_current_invoice_status := l_temp_invoice_status;
684         ELSE
685           IF (p_invoice_rec.awt_group_id is NULL AND
686               l_awt_group_id is NOT NULL) THEN
687             p_invoice_rec.awt_group_id := l_awt_group_id;
688           END IF;
689         END IF;
690 
691         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
692           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
693             '------------------>
694             l_temp_invoice_status  = '||l_temp_invoice_status);
695         END IF;
696        --bug6639866
697         ----------------------------------------------------------------------
698         -- Step 8.1
699         -- Check for Invalid pay AWT Group only if there is a valid Invoice No.
700         -- Also, populate pay_awt_group_id if all the following conditions are met:
701         -- 1) pay_awt_group_id is null
702         -- 2) pay_awt_group_id could be derived in the pay awt group check function
703         -- 3) the pay awt group check function returned that the invoice is valid
704         --    as far as pay awt group information is concerned.
705         ----------------------------------------------------------------------
706         debug_info := '(Check Invoice Validation 7) Check for pay AWT Group ,'
707                        ||'if Invoice No. is valid';
708         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
709           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
710                                         debug_info);
711         END IF;
712 
713         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_awt_group(
714            p_invoice_rec,                                             -- IN
715            p_pay_awt_group_id              => l_pay_awt_group_id,     -- OUT
716            p_default_last_updated_by   => p_default_last_updated_by,  -- IN
717            p_default_last_update_login => p_default_last_update_login,-- IN
718            p_current_invoice_status  => l_temp_invoice_status,      -- IN OUT
719            p_calling_sequence        => current_calling_sequence)
720               <> TRUE ) THEN
721           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
722             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
723               'v_check_invalid_pay_awt_group<-'||current_calling_sequence);
724           END IF;
725           RAISE check_inv_validation_failure;
726         END IF;
727 
728         --
729         IF (l_temp_invoice_status = 'N') THEN
730           l_current_invoice_status := l_temp_invoice_status;
731         ELSE
732         IF (p_invoice_rec.pay_awt_group_id is NULL AND
733               l_pay_awt_group_id is NOT NULL) THEN
734             p_invoice_rec.pay_awt_group_id := l_pay_awt_group_id;
735           END IF;
736         END IF;
737 
738         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
739           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
740             '------------------>
741             l_temp_invoice_status  = '||l_temp_invoice_status);
742         END IF;
743 
744         ----------------------------------------------------------------------
745         -- Step 9
746         -- Check for Invalid Exchange Rate Type only if there is a valid
747         -- Invoice No.
748         -- Also, populate exchange_rate, exchange_rate_type and
749         -- exchange_rate_date if all the following conditions are met:
750         -- 1) exchange_rate, exchange_rate_type and/or exchange_rate_date are
751         --    null
752         -- 2) the exchange rate type check could derived value for those
753         --    columns
754         -- 3) the exchange rate type check returned that the invoice is valid
755         --    as far as exchange rate is concerned.
756         ----------------------------------------------------------------------
757         debug_info := '(Check Invoice Validation 8) Check for Exchange Rate '
758                        ||'Type ,if Invoice No. is valid';
759         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
760           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
761                                         debug_info);
762         END IF;
763 
764         IF (AP_IMPORT_VALIDATION_PKG.v_check_exchange_rate_type (
765             p_invoice_rec,                                        -- IN
766             p_exchange_rate            => l_exchange_rate,        -- OUT
767             p_exchange_date            => l_exchange_date,        -- OUT
768             p_base_currency_code => p_base_currency_code,         -- IN
769             p_multi_currency_flag => p_multi_currency_flag,       -- IN
770             p_set_of_books_id => p_set_of_books_id,               -- IN
771             p_default_exchange_rate_type => p_default_exchange_rate_type, -- IN
772             p_make_rate_mandatory_flag => p_make_rate_mandatory_flag,  -- IN
773             p_default_last_updated_by => p_default_last_updated_by,    -- IN
774             p_default_last_update_login => p_default_last_update_login,-- IN
775             p_current_invoice_status    => l_temp_invoice_status, -- IN OUT
776             p_calling_sequence          => current_calling_sequence)
777               <> TRUE ) THEN
778           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
779             AP_IMPORT_UTILITIES_PKG.Print(
780               AP_IMPORT_INVOICES_PKG.g_debug_switch,
781               'v_check_exchange_rate_type<-'||current_calling_sequence);
782           END IF;
783           RAISE check_inv_validation_failure;
784         END IF;
785 
786         IF (l_temp_invoice_status = 'N') THEN
787           l_current_invoice_status := l_temp_invoice_status;
788         ELSE
789           IF (p_invoice_rec.exchange_rate_type IS NULL AND
790               p_default_exchange_rate_type IS NOT NULL AND
791               p_invoice_rec.invoice_currency_code <> p_base_currency_code) THEN
792             p_invoice_rec.exchange_rate_type := p_default_exchange_rate_type;
793           END IF;
794           IF (p_invoice_rec.exchange_rate is NULL AND
795               l_exchange_rate is NOT NULL) THEN
796             p_invoice_rec.exchange_rate := l_exchange_rate;
797           END IF;
798           IF (p_invoice_rec.exchange_date is NULL AND
799               l_exchange_date is NOT NULL) THEN
800             p_invoice_rec.exchange_date := l_exchange_date;
801           END IF;
802         END IF;
803 
804         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
805           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
806            '------------------>
807             l_temp_invoice_status  = '||l_temp_invoice_status);
808         END IF;
809 
810         ---------------------------------------------------------------------
811         -- Step 10
812         -- Check for Invalid Terms Info only if there is a valid Invoice No.
813         -- If PO Number exists then get terms from PO.
814         -- Also, populate terms_id and terms_date if all the following
815         -- conditions are met:
816         -- 1) terms id and/or terms date are null
817         -- 2) values for terms id and/or terms date could be derived
818         --    in the terms check function
819         -- 3) the terms date function returned that the invoice is valid
820         --    as far as terms are concerned.
821         ----------------------------------------------------------------------
822         debug_info := '(Check Invoice Validation 9) Check for Terms Info ,'
823                       ||'if Invoice No. is valid';
824         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
825           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
826                                         debug_info);
827         END IF;
828 
829         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_terms (
830               p_invoice_rec,                                         -- IN
831               p_terms_id                  => l_terms_id,             -- OUT
832               p_terms_date                => l_terms_date,           -- OUT
833               p_terms_date_basis          => l_terms_date_basis,     -- IN
834               p_default_last_updated_by => p_default_last_updated_by,    -- IN
835               p_default_last_update_login => p_default_last_update_login,-- IN
836               p_current_invoice_status    => l_temp_invoice_status,  -- IN OUT
837               p_calling_sequence          => current_calling_sequence)
838               <> TRUE ) THEN
839           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
840         AP_IMPORT_UTILITIES_PKG.Print(
841         AP_IMPORT_INVOICES_PKG.g_debug_switch,
842                 'v_check_invalid_terms<-'||current_calling_sequence);
843           END IF;
844           RAISE check_inv_validation_failure;
845         END IF;
846 
847         IF (l_temp_invoice_status = 'N') THEN
848           l_current_invoice_status := l_temp_invoice_status;
849         ELSE
850           IF (p_invoice_rec.terms_id is NULL AND
851               l_terms_id is NOT NULL) THEN
852             p_invoice_rec.terms_id := l_terms_id;
853         END IF;
854       IF (p_invoice_rec.terms_date IS NULL AND
855           l_terms_date IS NOT NULL) THEN
856         p_invoice_rec.terms_date := l_terms_date;
857       END IF;
858         END IF;
859 
860         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
861           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
862             '------------------>
863             l_temp_invoice_status  = '||l_temp_invoice_status
864             ||'terms_id = '||to_char(l_terms_id) );
865         END IF;
866 
867         ----------------------------------------------------------------------
868         -- Step 11
869         -- Check for Misc Invoice info
870         ----------------------------------------------------------------------
871         debug_info := '(Check Invoice Validation 10) Check for Misc Info ';
872         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
873           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
874                                         debug_info);
875         END IF;
876         IF (AP_IMPORT_VALIDATION_PKG.v_check_misc_invoice_info (
877               p_invoice_rec,                                         -- IN
878               p_set_of_books_id,                                     -- IN
879               p_default_last_updated_by,                             -- IN
880               p_default_last_update_login,                           -- IN
881               p_current_invoice_status     => l_temp_invoice_status, -- IN OUT
882               p_calling_sequence           => current_calling_sequence)
883               <> TRUE ) THEN
884           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
885             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
886               'v_check_misc_invoice_info<-'||current_calling_sequence);
887           END IF;
888           RAISE check_inv_validation_failure;
889         END IF;
890 
891         IF (l_temp_invoice_status = 'N') THEN
892           l_current_invoice_status := l_temp_invoice_status;
893         END IF;
894 
895         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
896           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
897             '------------------>
898             l_temp_invoice_status  = '||l_temp_invoice_status);
899         END IF;
900 
901          /* -------------------------------------------------------------------
902             Step 11a: Get/Validate Legal Entity Information
903                There are two forms of LE derivation.
904                1) Internal products could optionally pass the LE in the
905                   LEGAL_ENTITY_ID Column. This will be validated by the API
906                   provided by LE Team.
907 
908                2)For the invoices coming via EDI, XML, they could
909                  provide us with Customer Registration CODE/Numbers, which
910                  will be used to derive the LE using a LE API.
911         --------------------------------------------------------------------*/
912         debug_info := '(Check Invoice Validation 11a) Check for LE Info ';
913         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
914           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
915                                         debug_info);
916         END IF;
917 
918         IF (AP_IMPORT_VALIDATION_PKG.v_check_Legal_Entity_info (
919               p_invoice_rec,                                         -- IN OUT
920               p_set_of_books_id,                                     -- IN
921               p_default_last_updated_by,                             -- IN
922               p_default_last_update_login,                           -- IN
923               p_current_invoice_status     => l_temp_invoice_status, -- IN OUT
924               p_calling_sequence           => current_calling_sequence)
925               <> TRUE ) THEN
926           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
927             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
928               'v_check_Legal_Entity_info<-'||current_calling_sequence);
929           END IF;
930           RAISE check_inv_validation_failure;
931         END IF;
932 
933         IF (l_temp_invoice_status = 'N') THEN
934           l_current_invoice_status := l_temp_invoice_status;
935         END IF;
936 
937         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
938           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
939             '------------------>
940             l_temp_invoice_status  = '||l_temp_invoice_status);
941         END IF;
942 
943         ----------------------------------------------------------------------
944         -- Step 12
945         -- Check for Invalid Payment Currency Info only if there is a valid
946         -- Invoice No.
947         -- Also, populate payment_currency_code and payment cross rate
948         -- information if all the following conditions are met:
949         -- 1) payment currency code and/or payment cross rate information are
950         --    null
951         -- 2) payment currency code and/or payment cross rate information was
952         --    derived as part of the pay curr check.
953         -- 3) the pay curr check function returned that the invoice is valid
954         --    as far as pay curr info is concerned.
955         ----------------------------------------------------------------------
956         debug_info := '(Check Invoice Validation 11) Check for '||
957                        'Payment Currency Info ,if Invoice No. is valid';
958         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
959           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
960           debug_info);
961         END IF;
962 
963         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_curr (
964               p_invoice_rec,                                           -- IN
965               p_pay_currency_code            => l_pay_currency_code,   -- OUT
966               p_payment_cross_rate_date      => l_pay_cross_rate_date, -- OUT
967               p_payment_cross_rate           => l_pay_cross_rate,      --OUT
968               p_payment_cross_rate_type      => l_pay_cross_rate_type, --OUT
969               p_default_last_updated_by   => p_default_last_updated_by,-- IN
970               p_default_last_update_login => p_default_last_update_login,-- IN
971               p_current_invoice_status    => l_temp_invoice_status, -- IN OUT
972               p_calling_sequence          => current_calling_sequence)
973               <> TRUE ) THEN
974           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
975             AP_IMPORT_UTILITIES_PKG.Print(
976               AP_IMPORT_INVOICES_PKG.g_debug_switch,
977               'v_check_invalid_pay_curr<-'||current_calling_sequence);
978           END IF;
979           RAISE check_inv_validation_failure;
980         END IF;
981 
982         IF (l_temp_invoice_status = 'N') THEN
983           l_current_invoice_status := l_temp_invoice_status;
984         ELSE
985           IF (p_invoice_rec.payment_currency_code is NULL AND
986               l_pay_currency_code is NOT NULL) THEN
987             p_invoice_rec.payment_currency_code := l_pay_currency_code;
988           END IF;
989           IF (p_invoice_rec.payment_cross_rate_date is NULL AND
990               l_pay_cross_rate_date is NOT NULL) THEN
991             p_invoice_rec.payment_cross_rate_date := l_pay_cross_rate_date;
992           END IF;
993           IF ((p_invoice_rec.payment_cross_rate is NULL AND
994                l_pay_cross_rate is NOT NULL) OR
995           (p_invoice_rec.payment_cross_rate is NOT NULL AND
996            l_pay_cross_rate is NOT NULL AND
997            p_invoice_rec.payment_cross_rate <> l_pay_cross_rate)) THEN
998             p_invoice_rec.payment_cross_rate := l_pay_cross_rate;
999           END IF;
1000           IF (p_invoice_rec.payment_cross_rate_type is NULL AND
1001               l_pay_cross_rate_type is NOT NULL) THEN
1002             p_invoice_rec.payment_cross_rate_type := l_pay_cross_rate_type;
1003           END IF;
1004         END IF;
1005         --
1006         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1007           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1008             '------------------>
1009             l_temp_invoice_status  = '||l_temp_invoice_status);
1010         END IF;
1011 
1012 /* Bug 4014019: Commenting the call to jg_globe_flex_val due to build issues.
1013 
1014         ----------------------------------------------------------------------
1015         -- Step 13
1016         -- Check for Invalid Global Flexfield Value.
1017         -- Retropricing: This may require JG modifications as parent table can
1018         -- now also be the Temp table AP_PPA_INVOICES_GT
1019         ----------------------------------------------------------------------
1020         debug_info := '(Check Invoice Validation 13) Check for GDFF';
1021         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1022           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1023                                         debug_info);
1024         END IF;
1025         jg_globe_flex_val.check_attr_value(
1026                       'APXIIMPT',
1027                       p_invoice_rec.global_attribute_category,
1028                       p_invoice_rec.global_attribute1,
1029                       p_invoice_rec.global_attribute2,
1030                       p_invoice_rec.global_attribute3,
1031                       p_invoice_rec.global_attribute4,
1032                       p_invoice_rec.global_attribute5,
1033                       p_invoice_rec.global_attribute6,
1034                       p_invoice_rec.global_attribute7,
1035                       p_invoice_rec.global_attribute8,
1036                       p_invoice_rec.global_attribute9,
1037                       p_invoice_rec.global_attribute10,
1038                       p_invoice_rec.global_attribute11,
1039                       p_invoice_rec.global_attribute12,
1040                       p_invoice_rec.global_attribute13,
1041                       p_invoice_rec.global_attribute14,
1042                       p_invoice_rec.global_attribute15,
1043                       p_invoice_rec.global_attribute16,
1044                       p_invoice_rec.global_attribute17,
1045                       p_invoice_rec.global_attribute18,
1046                       p_invoice_rec.global_attribute19,
1047                       p_invoice_rec.global_attribute20,
1048                       TO_CHAR(p_set_of_books_id),
1049                       fnd_date.date_to_canonical(p_invoice_rec.invoice_date),
1050                       AP_IMPORT_INVOICES_PKG.g_invoices_table,  --Retropricing
1051                       TO_CHAR(p_invoice_rec.invoice_id),
1052                       TO_CHAR(p_default_last_updated_by),
1053                       TO_CHAR(p_default_last_update_login),
1054                       current_calling_sequence,
1055                       TO_CHAR(p_invoice_rec.vendor_site_id), -- arg 8
1056                       p_invoice_rec.payment_currency_code,   -- arg 9
1057                       NULL,NULL,NULL,NULL,NULL,NULL,NULL,
1058                       NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,
1059                       NULL,NULL,NULL,NULL,
1060                       p_current_status => l_temp_invoice_status);
1061 
1062         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1063           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1064             'Global Flexfield Header Processed  '|| l_temp_invoice_status);
1065           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1066             'Invoice_id  '|| to_char(p_invoice_rec.invoice_id));
1067         END IF;
1068         IF (l_temp_invoice_status = 'N') THEN
1069           l_current_invoice_status := l_temp_invoice_status;
1070         END IF;
1071 
1072 */
1073 
1074         ----------------------------------------------------------------------
1075         -- Step 14
1076         -- Check for Valid Prepayment Info.
1077         -- Retropricing: All prepayment fields will be NULL for PPA's
1078         ----------------------------------------------------------------------
1079         IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
1080             debug_info :=
1081                      '(Check Invoice Validation 14) Check for Prepayment Info.';
1082             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1083               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1084                                             debug_info);
1085             END IF;
1086 
1087             IF (AP_IMPORT_VALIDATION_PKG.v_check_prepay_info(
1088                   p_invoice_rec,                                       -- IN OUT
1089                   p_base_currency_code,                                -- IN
1090                   p_prepay_period_name,                                -- IN OUT
1091 		  p_prepay_invoice_id,				       -- OUT
1092 		  p_prepay_case_name,				       -- OUT
1093                   p_request_id,                                        -- IN
1094                   p_default_last_updated_by,                           -- IN
1095                   p_default_last_update_login,                         -- IN
1096                   p_current_invoice_status   => l_temp_invoice_status, -- IN OUT
1097                   p_calling_sequence         => current_calling_sequence)
1098                   <> TRUE ) THEN
1099               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1100                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1101                   'v_check_prepay_info<-' ||current_calling_sequence);
1102               END IF;
1103               RAISE check_inv_validation_failure;
1104 
1105             END IF;
1106 
1107             IF (l_temp_invoice_status = 'N') THEN
1108               l_current_invoice_status := l_temp_invoice_status;
1109             END IF;
1110 
1111             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1112               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1113                             '------------------>
1114                       l_temp_invoice_status  = '||l_temp_invoice_status);
1115             END IF;
1116         END IF;
1117         ----------------------------------------------------------------------
1118         -- Step 15
1119         -- Check for Tax info at invoice level
1120         -- Although all eTax related fields(control_amount,tax_related_invoice_id,
1121         -- calc_tax_during_import_flag will be NULL on the Invoice Header
1122         -- some sql statemnts in the v_check_tax_info will get executed.
1123         ----------------------------------------------------------------------
1124         IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
1125             debug_info :=
1126               '(Check Invoice Validation 15) Check for tax drivers or invoice level '||
1127               'tax validations.';
1128             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1129               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1130                                             debug_info);
1131             END IF;
1132 
1133             IF (AP_IMPORT_VALIDATION_PKG.v_check_tax_info(
1134                p_invoice_rec                => p_invoice_rec,
1135                p_default_last_updated_by    => p_default_last_updated_by,
1136                p_default_last_update_login  => p_default_last_update_login,
1137                p_current_invoice_status     => l_temp_invoice_status,
1138                p_calling_sequence           => current_calling_sequence)
1139                   <> TRUE ) THEN
1140 
1141               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1142                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1143                   'v_check_tax_info<-' ||current_calling_sequence);
1144               END IF;
1145               RAISE check_inv_validation_failure;
1146 
1147             END IF;
1148 
1149             IF (l_temp_invoice_status = 'N') THEN
1150               l_current_invoice_status := l_temp_invoice_status;
1151             END IF;
1152 
1153             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1154               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1155                 '------------------> l_temp_invoice_status  = '
1156                 ||l_temp_invoice_status);
1157 
1158             END IF;
1159         END IF;
1160 
1161    ------------------------------------------------
1162     -- Step 16
1163     -- Check for Invalid Remit to Supplier
1164    ------------------------------------------------
1165 
1166    debug_info := 'Check for Invalid Remit to Supplier';
1167         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1168           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1169                                   debug_info);
1170         END IF;
1171 
1172         IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_remit_supplier (
1173             p_invoice_rec			=>	p_invoice_rec, -- IN OUT
1174             p_default_last_updated_by =>	p_default_last_updated_by, -- IN
1175             p_default_last_update_login =>	p_default_last_update_login,                           -- IN
1176             p_current_invoice_status     =>	l_temp_invoice_status, -- IN OUT
1177             p_calling_sequence		=>	current_calling_sequence) <> TRUE )THEN
1178 	      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1179 		  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1180 			'v_check_invalid_remit_supplier<-'||current_calling_sequence);
1181 	      END IF;
1182 	      RAISE check_inv_validation_failure;
1183         END IF;
1184 
1185 	IF (l_temp_invoice_status = 'N') THEN
1186               l_current_invoice_status := l_temp_invoice_status;
1187         END IF;
1188 
1189 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1190 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1191 		'------------------> l_temp_invoice_status  = '
1192 		||l_temp_invoice_status);
1193 	END IF;
1194 
1195         ----------------------------------------------------------------------
1196         -- Step 17
1197         -- Check for User Xrate information
1198         -- Also populate no_xrate_base_amount to be used as base amount if
1199         -- the following conditions are met:
1200         -- 1) no_xrate_base_amount is null
1201         -- 2) invoice currency code is different than base currency
1202         -- 3) base amount could be derived as part of no xrate base amt check
1203         -- 4) no xrate base amount check function returned that the invoice
1204         --    is valid as far as xrate is concerned.
1205         -- Retropricing:
1206         -- Although the function calculates invoice_base_amount, for PPA's the
1207         -- base_Amount is provided in the PPA Invoice. Also since base amounts
1208         -- are re-calculated during validation, there is no need to call the
1209         -- validation below for PPA's
1210         ----------------------------------------------------------------------
1211         IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
1212             debug_info :=
1213                     '(Check Invoice Validation 16) Check for Exchange Rate Info.';
1214             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1215               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1216                                             debug_info);
1217             END IF;
1218 
1219             IF (AP_IMPORT_VALIDATION_PKG.v_check_no_xrate_base_amount (
1220                   p_invoice_rec,                                          -- IN
1221                   p_base_currency_code,                                   -- IN
1222                   p_multi_currency_flag,                                  -- IN
1223                   p_calc_user_xrate,                                      -- IN
1224                   p_default_last_updated_by,                              -- IN
1225                      p_default_last_update_login,                            -- IN
1226                   p_invoice_base_amount        => l_invoice_base_amount,  -- OUT
1227                   p_current_invoice_status     => l_temp_invoice_status,  -- IN OUT
1228                   p_calling_sequence           => current_calling_sequence)
1229                   <> TRUE ) THEN
1230               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1231                   AP_IMPORT_UTILITIES_PKG.Print(
1232                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
1233                     'v_check_inavlid_currency_code<-' ||current_calling_sequence);
1234               END IF;
1235               RAISE check_inv_validation_failure;
1236             END IF;
1237 
1238             IF (l_temp_invoice_status = 'N' )THEN
1239               l_current_invoice_Status := l_temp_invoice_status;
1240             ELSE
1241               IF (p_invoice_rec.no_xrate_base_amount IS NULL AND
1242                   l_invoice_base_amount IS NOT NULL AND
1243                   p_invoice_rec.invoice_currency_code <> p_base_currency_code) THEN
1244                  p_invoice_rec.no_xrate_base_amount := l_invoice_base_amount;
1245               END IF;
1246             END IF;
1247         END IF;  --Retropricing
1248 
1249         debug_info := '(Check Invoice Validation 17) Check Payment Info ';
1250         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1251           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1252                                         debug_info);
1253         END IF;
1254 
1255         IF (AP_IMPORT_VALIDATION_PKG.v_check_payment_defaults (
1256               p_invoice_rec,
1257               l_temp_invoice_status,
1258               current_calling_sequence,
1259               p_default_last_updated_by,
1260               p_default_last_update_login)
1261               <> TRUE ) THEN
1262           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1263             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1264               'v_check_payment_defaults<-'||current_calling_sequence);
1265           END IF;
1266           RAISE check_inv_validation_failure;
1267         END IF;
1268 
1269         IF (l_temp_invoice_status = 'N') THEN
1270           l_current_invoice_status := l_temp_invoice_status;
1271         END IF;
1272 
1273         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1274           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1275             '------------------>
1276             l_temp_invoice_status  = '||l_temp_invoice_status);
1277         END IF;
1278 
1279 
1280 
1281 
1282 
1283 
1284 
1285       END IF; -- status not N after validating invoice number
1286 
1287     ELSE -- IF (p_invoice_rec.vendor_site_id or party_site_id is NOT NULL)
1288       -- fatal error - no valid vendor site found - stop processing for
1289       -- this invoice.  A row was already inserted into
1290       -- AP_INTERFACE_REJECTIONS within CHECK_INVALID_SUPPLIER_SITE
1291       p_fatal_error_flag := 'Y';
1292       l_current_invoice_status := 'N';
1293     END IF; -- IF (p_invoice_rec.vendor_site_id is NOT NULL) THEN
1294 
1295   ELSE -- IF (p_invoice_rec.vendor_id or party_id is NOT NULL)
1296     -- fatal error - no valid vendor found - stop processing for this
1297     -- invoice.  A row was already inserted into AP_INTERFACE_REJECTIONS
1298     -- within CHECK_INVALID_SUPPLIER
1299     p_fatal_error_flag := 'Y';
1300     l_current_invoice_status := 'N';
1301   END IF; -- IF (p_invoice_rec.vendor_id or party_id is NOT NULL)
1302 
1303   p_current_invoice_status := l_current_invoice_status;
1304 
1305 RETURN (TRUE);
1306 
1307 EXCEPTION
1308   WHEN OTHERS THEN
1309     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1310       AP_IMPORT_UTILITIES_PKG.Print(
1311         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
1312     END IF;
1313 
1314     IF (SQLCODE < 0) then
1315       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1316         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
1317       END IF;
1318     END IF;
1319     RETURN(FALSE);
1320 
1321 END v_check_invoice_validation;
1322 
1323 
1324 -----------------------------------------------------------------------------
1325 -- This function is used to perform PO validation.
1326 --
1327 FUNCTION v_check_invalid_po (
1328            p_invoice_rec    IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
1329            p_default_last_updated_by   IN             NUMBER,
1330            p_default_last_update_login IN             NUMBER,
1331            p_current_invoice_status    IN OUT NOCOPY  VARCHAR2,
1332            p_po_vendor_id                 OUT NOCOPY  NUMBER,
1333            p_po_vendor_site_id            OUT NOCOPY  NUMBER,
1334            p_po_exists_flag               OUT NOCOPY  VARCHAR2,
1335            p_calling_sequence          IN             VARCHAR2) RETURN BOOLEAN
1336 IS
1337 
1338 invalid_po_check_failure    EXCEPTION;
1339 l_current_invoice_status    VARCHAR2(1) := 'Y';
1340 l_closed_date               DATE;
1341 l_vendor_id                 NUMBER;
1342 l_vendor_site_id            NUMBER;
1343 l_po_exists_flag            VARCHAR2(1) := 'N';
1344 current_calling_sequence    VARCHAR2(2000);
1345 debug_info                  VARCHAR2(500);
1346 l_invoice_vendor_name       po_vendors.vendor_name%TYPE := '';
1347 
1348 BEGIN
1349   -- Update the calling sequence
1350   --
1351   current_calling_sequence :=  'AP_IMPORT_VALIDATION_PKG.v_check_invalid_po<-'
1352                                 ||P_calling_sequence;
1353 
1354   -- differentiate PO from RFQ and Quotation
1355   SELECT closed_date, vendor_id, vendor_site_id
1356     INTO l_closed_date ,l_vendor_id, l_vendor_site_id
1357     FROM po_headers
1358    WHERE segment1 = p_invoice_rec.po_number
1359      AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
1360    /* BUG  2902452 added*/
1361    AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
1362 
1363   IF (l_vendor_id IS NOT NULL) Then
1364     l_po_exists_flag := 'Y';
1365   END IF;
1366 
1367   --------------------------------------------------------------------------
1368   -- Step 1
1369   -- Check for Inactive PO NUMBER.
1370   --------------------------------------------------------------------------
1371   debug_info := '(Check PO Number 1) Check for Inactive PO Number.';
1372   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1373     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1374                                   debug_info);
1375   END IF;
1376   --Bypass this rejections for PPA's  --Retropricing
1377   IF (l_closed_date is not null AND
1378       AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
1379     -- PO has been closed
1380     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
1381           AP_IMPORT_INVOICES_PKG.g_invoices_table,
1382           p_invoice_rec.invoice_id,
1383           'INACTIVE PO',
1384           p_default_last_updated_by,
1385           p_default_last_update_login,
1386           current_calling_sequence) <> TRUE) THEN
1387       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1388         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1389                                       'insert_rejections<-'||
1390                                       current_calling_sequence);
1391       END IF;
1392       RAISE invalid_po_check_failure;
1393     END IF;
1394 
1395     l_current_invoice_status := 'N';
1396 
1397   ELSE
1398     ------------------------------------------------------------------------
1399     -- Step 2
1400     -- Check for Inconsistent PO Vendor.
1401     ------------------------------------------------------------------------
1402     debug_info := '(Check PO Number 2) Check for Inconsistent PO Vendor.';
1403     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1404       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1405                                     debug_info);
1406     END IF;
1407 
1408     IF (l_vendor_id <> nvl(p_invoice_rec.vendor_id, l_vendor_id)) THEN
1409     --Retropricing There is no need for the IF statement mentioned below
1410       IF (AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY' ) THEN
1411         BEGIN
1412           -- Get contextual Information for XML Gateway
1413           SELECT vendor_name
1414             INTO l_invoice_vendor_name
1415             FROM po_vendors
1416            WHERE vendor_id = p_invoice_rec.vendor_id;
1417 
1418       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1419               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1420                p_invoice_rec.invoice_id,
1421                'INCONSISTENT PO SUPPLIER',
1422                p_default_last_updated_by,
1423                p_default_last_update_login,
1424                current_calling_sequence,
1425                'Y',
1426                'SUPPLIER NAME',
1427                l_invoice_vendor_name) <> TRUE) THEN
1428             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1429               AP_IMPORT_UTILITIES_PKG.Print(
1430                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
1431                 'insert_rejections<-'||current_calling_sequence);
1432             END IF;
1433             RAISE invalid_po_check_failure;
1434           END IF;
1435 
1436         EXCEPTION
1437           WHEN NO_DATA_FOUND THEN
1438             NULL;
1439         END;
1440       ELSE
1441         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1442              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1443               p_invoice_rec.invoice_id,
1444               'INCONSISTENT PO SUPPLIER',
1445               p_default_last_updated_by,
1446               p_default_last_update_login,
1447               current_calling_sequence) <> TRUE) THEN
1448           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1449             AP_IMPORT_UTILITIES_PKG.Print(
1450               AP_IMPORT_INVOICES_PKG.g_debug_switch,
1451               'insert_rejections<-'||
1452               current_calling_sequence);
1453           END IF;
1454           RAISE invalid_po_check_failure;
1455         END IF;
1456 
1457       END IF; -- g_source = 'XML GATEWAY'
1458 
1459       l_current_invoice_status := 'N';
1460 
1461     END IF; -- vendor id <> vendor id on interface invoice
1462   END IF;  -- closed date is not null
1463 
1464   p_po_vendor_id := l_vendor_id;
1465   p_po_vendor_site_id := l_vendor_site_id;
1466   p_po_exists_flag := l_po_exists_flag;
1467   p_current_invoice_status := l_current_invoice_status;
1468   RETURN (TRUE);
1469 
1470 EXCEPTION
1471   WHEN no_data_found THEN
1472 
1473     -------------------------------------------------------------------------
1474     -- Step 3
1475     -- Invalid PO NUMBER.
1476     -------------------------------------------------------------------------
1477     debug_info := '(Check PO Number 3) Check for Invalid PO Number.';
1478     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1479       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1480                                     debug_info);
1481     END IF;
1482 
1483     -- include context for XML GATEWAY
1484     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1485                           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1486                             p_invoice_rec.invoice_id,
1487                            'INVALID PO NUM',
1488                             p_default_last_updated_by,
1489                             p_default_last_update_login,
1490                             current_calling_sequence,
1491                             'Y',
1492                             'PO NUMBER',
1493                             p_invoice_rec.po_number) <> TRUE) THEN
1494       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1495         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1496                                       'insert_rejections<-'||
1497                                        current_calling_sequence);
1498       END IF;
1499       RAISE invalid_po_check_failure;
1500     END IF;
1501 
1502     p_po_exists_flag := l_po_exists_flag;
1503     l_current_invoice_status := 'N';
1504     p_current_invoice_status := l_current_invoice_status;
1505     RETURN (TRUE);
1506 
1507   WHEN OTHERS THEN
1508     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1509       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1510                                     debug_info);
1511     END IF;
1512 
1513     IF (SQLCODE < 0) then
1514       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1515         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1516                                       SQLERRM);
1517       END IF;
1518     END IF;
1519     RETURN(FALSE);
1520 
1521 END v_check_invalid_po;
1522 
1523 
1524 -----------------------------------------------------------------------------
1525 -- This function is used to perform Supplier validation
1526 --
1527 -----------------------------------------------------------------------------
1528 FUNCTION v_check_invalid_supplier(
1529          p_invoice_rec   IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
1530          p_default_last_updated_by     IN            NUMBER,
1531          p_default_last_update_login   IN            NUMBER,
1532          p_return_vendor_id               OUT NOCOPY NUMBER,
1533          p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
1534          p_calling_sequence            IN            VARCHAR2)
1535 RETURN BOOLEAN IS
1536 
1537 supplier_check_failure      EXCEPTION;
1538 l_vendor_id                 PO_VENDORS.VENDOR_ID%TYPE :=
1539                               p_invoice_rec.vendor_id;
1540 l_vendor_id_per_num         PO_VENDORS.VENDOR_ID%TYPE;
1541 l_vendor_id_per_name        PO_VENDORS.VENDOR_ID%TYPE;
1542 l_current_invoice_status    VARCHAR2(1) := 'Y';
1543 return_vendor_id            NUMBER(15);
1544 current_calling_sequence    VARCHAR2(2000);
1545 debug_info                  VARCHAR2(500);
1546 
1547 
1548 BEGIN
1549   -- Update the calling sequence
1550   --
1551   current_calling_sequence :=
1552     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier<-'
1553     ||P_calling_sequence;
1554 
1555   IF ((p_invoice_rec.vendor_id is NULL) AND
1556       (p_invoice_rec.vendor_num is NULL) AND
1557       (p_invoice_rec.vendor_name is NULL)) THEN
1558 
1559     -------------------------------------------------------------------------
1560     -- Step 1
1561     -- Check for Null Supplier.
1562     -------------------------------------------------------------------------
1563     debug_info := '(Check Invalid Supplier 1) Check for Null Supplier.';
1564     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1565       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1566                                     debug_info);
1567     END IF;
1568 
1569     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1570             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1571              p_invoice_rec.invoice_id,
1572              'NO SUPPLIER',
1573              p_default_last_updated_by,
1574              p_default_last_update_login,
1575              current_calling_sequence) <> TRUE) THEN
1576       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1577         AP_IMPORT_UTILITIES_PKG.Print(
1578           AP_IMPORT_INVOICES_PKG.g_debug_switch,
1579           'insert_rejections<-'||current_calling_sequence);
1580       END IF;
1581       RAISE supplier_check_failure;
1582     END IF;
1583     return_vendor_id := null;
1584 
1585   ELSE
1586 
1587      IF (p_invoice_rec.vendor_id is NOT NULL) THEN
1588 
1589        ----------------------------------------------------------------------
1590        -- Step 2
1591        -- validate vendor id
1592        ----------------------------------------------------------------------
1593        debug_info := '(Check Invalid Supplier 2) Validate vendor id.';
1594        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1595          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1596                                        debug_info);
1597        END IF;
1598 
1599        SELECT vendor_id
1600          INTO l_vendor_id
1601          FROM po_vendors pv
1602         WHERE vendor_id = p_invoice_rec.vendor_id
1603           AND nvl(trunc(PV.START_DATE_ACTIVE),
1604                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
1605               <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
1606           AND nvl(trunc(PV.END_DATE_ACTIVE),
1607                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1608               > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1609 
1610      END IF;
1611 
1612      IF (p_invoice_rec.vendor_num is NOT NULL) THEN
1613 
1614        ----------------------------------------------------------------------
1615        -- Step 3
1616        -- Validate vendor number and retrieve vendor id
1617        ----------------------------------------------------------------------
1618        debug_info := '(Check Invalid Supplier 3) Validate vendor number and '
1619                       ||'retrieve vendor id';
1620        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1621          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1622                                        debug_info);
1623        END IF;
1624 
1625        SELECT vendor_id
1626          INTO l_vendor_id_per_num
1627          FROM po_vendors PV
1628         WHERE segment1 = p_invoice_rec.vendor_num
1629           AND nvl(trunc(PV.START_DATE_ACTIVE),
1630                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
1631               <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
1632           AND nvl(trunc(PV.END_DATE_ACTIVE),
1633                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1634               > AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
1635 
1636      END IF;
1637 
1638      IF (p_invoice_rec.vendor_name is NOT NULL) THEN
1639 
1640        ----------------------------------------------------------------------
1641        -- Step 4
1642        -- Validate vendor name and retrieve vendor id
1643        ----------------------------------------------------------------------
1644        debug_info := '(Check Invalid Supplier 4) Validate vendor name and '
1645                      ||'retrieve vendor id';
1646        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1647          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1648                                        debug_info);
1649        END IF;
1650 
1651        SELECT vendor_id
1652          INTO l_vendor_id_per_name
1653          FROM po_vendors PV
1654         WHERE vendor_name = p_invoice_rec.vendor_name
1655           AND nvl(trunc(PV.START_DATE_ACTIVE),
1656                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
1657               <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
1658           AND nvl(trunc(PV.END_DATE_ACTIVE),
1659                   AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1660               > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1661 
1662      END IF;
1663 
1664      IF ((l_vendor_id is NOT NULL)                           AND
1665                  (((l_vendor_id_per_num is NOT NULL) AND
1666                    (l_vendor_id <> l_vendor_id_per_num))     OR
1667                  ((l_vendor_id_per_name is NOT NULL) AND
1668                   (l_vendor_id <> l_vendor_id_per_name)))
1669         ) THEN
1670 
1671        -----------------------------------------------------------------------
1672        -- Step 5
1673        -- Check for Inconsitent Supplier based on not null supplier id provided
1674        -----------------------------------------------------------------------
1675        debug_info := '(Check Invalid Supplier 5) Check for inconsistent '
1676                      ||'Supplier - supplier id not null';
1677        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1678          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1679                                        debug_info);
1680        END IF;
1681 
1682        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1683                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1684                         p_invoice_rec.invoice_id,
1685                         'INCONSISTENT SUPPLIER',
1686                         p_default_last_updated_by,
1687                         p_default_last_update_login,
1688                         current_calling_sequence) <> TRUE) THEN
1689          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1690            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1691                                          'insert_rejections<-'
1692                                           ||current_calling_sequence);
1693          END IF;
1694          RAISE supplier_check_failure;
1695        END IF;
1696 
1697        l_current_invoice_status := 'N';
1698 
1699      END IF;
1700 
1701 
1702      IF ((l_vendor_id_per_num is NOT NULL) AND
1703          (l_vendor_id_per_name is NOT NULL) AND
1704          (l_vendor_id_per_num <> l_vendor_id_per_name) AND
1705          (l_current_invoice_status = 'Y')) THEN
1706 
1707        ----------------------------------------------------------------------
1708        -- Step 6
1709        -- Check for Inconsitent Supplier number and Name.
1710        ----------------------------------------------------------------------
1711        debug_info := '(Check Invalid Supplier 6) Check for inconsistent '
1712                      ||'Supplier Number and Name.';
1713        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1714          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1715                                        debug_info);
1716        END IF;
1717 
1718        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1719                   (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1720                    p_invoice_rec.invoice_id,
1721                    'INCONSISTENT SUPPLIER',
1722                    p_default_last_updated_by,
1723                    p_default_last_update_login,
1724                    current_calling_sequence) <> TRUE) THEN
1725          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1726            AP_IMPORT_UTILITIES_PKG.Print(
1727              AP_IMPORT_INVOICES_PKG.g_debug_switch,
1728              'insert_rejections<-'||current_calling_sequence);
1729          END IF;
1730          RAISE supplier_check_failure;
1731        END IF;
1732 
1733        l_current_invoice_status := 'N';
1734 
1735      END IF;
1736 
1737      IF (l_current_invoice_status = 'Y') THEN
1738 
1739        ----------------------------------------------------------------------
1740        -- Step 7
1741        -- Save Supplier id for further processing.
1742        ----------------------------------------------------------------------
1743        debug_info := '(Check Invalid Supplier 7) Save Supplier id for '
1744                      ||'further processing.';
1745        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1746          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1747                                        debug_info);
1748        END IF;
1749 
1750        IF (l_vendor_id is NULL) THEN
1751 
1752          IF (l_vendor_id_per_num is NOT NULL) THEN
1753            return_vendor_id := l_vendor_id_per_num;
1754          ELSE
1755            return_vendor_id := l_vendor_id_per_name;
1756          END IF;
1757        ELSE
1758          return_vendor_id := l_vendor_id;
1759        END IF;
1760      END IF;
1761 
1762   END IF;
1763   p_return_vendor_id := return_vendor_id;
1764   p_current_invoice_status := l_current_invoice_status;
1765   RETURN (TRUE);
1766 EXCEPTION
1767   WHEN no_data_found THEN
1768 
1769     -------------------------------------------------------------------------
1770     -- Step 8
1771     -- Check for invalid Supplier.
1772     -------------------------------------------------------------------------
1773     debug_info := '(Check Invalid Supplier 8) Check for invalid Supplier.';
1774     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1775       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1776                                     debug_info);
1777     END IF;
1778 
1779     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1780                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1781                 p_invoice_rec.invoice_id,
1782                 'INVALID SUPPLIER',
1783                 p_default_last_updated_by,
1784                 p_default_last_update_login,
1785                 current_calling_sequence) <> TRUE) THEN
1786       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1787         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1788           'insert_rejections<-'||current_calling_sequence);
1789       END IF;
1790       RAISE supplier_check_failure;
1791 
1792     END IF;
1793     l_current_invoice_status := 'N';
1794     p_return_vendor_id := return_vendor_id;
1795     p_current_invoice_status := l_current_invoice_status;
1796     RETURN (TRUE);
1797 
1798 
1799   WHEN OTHERS THEN
1800     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1801       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1802                                     debug_info);
1803     END IF;
1804 
1805     IF (SQLCODE < 0) then
1806       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1807         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1808                                       SQLERRM);
1809       END IF;
1810     END IF;
1811     RETURN(FALSE);
1812 
1813 END v_check_invalid_supplier;
1814 
1815 
1816 ------------------------------------------------------------------
1817 -- This function is used to perform Supplier Site validation
1818 --
1819 ------------------------------------------------------------------
1820 FUNCTION v_check_invalid_supplier_site (
1821          p_invoice_rec  IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
1822          p_vendor_site_id_per_po      IN            NUMBER,
1823          p_default_last_updated_by    IN            NUMBER,
1824          p_default_last_update_login  IN            NUMBER,
1825          p_return_vendor_site_id         OUT NOCOPY NUMBER,
1826          p_terms_date_basis              OUT NOCOPY VARCHAR2,
1827          p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
1828          p_calling_sequence           IN VARCHAR2) RETURN BOOLEAN
1829 IS
1830 
1831 supplier_site_check_failure        EXCEPTION;
1832 l_vendor_site_id                   NUMBER(15);
1833 l_vendor_site_id_per_code          NUMBER(15);
1834 l_check_vendor_id                  NUMBER;
1835 l_current_invoice_status           VARCHAR2(1):='Y';
1836 l_valid_vendor                     VARCHAR2(1);
1837 return_vendor_site_id              NUMBER(15);
1838 l_pay_site_flag                    VARCHAR2(1);
1839 l_pay_site_flag_per_code           VARCHAR2(1);
1840 current_calling_sequence           VARCHAR2(2000);
1841 debug_info                         VARCHAR2(500);
1842 
1843 BEGIN
1844   -- Update the calling sequence
1845   --
1846   current_calling_sequence :=
1847     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_supplier_site<-'
1848      ||P_calling_sequence;
1849 
1850   debug_info := '(Check Invalid Site 1) Check Supplier Site';
1851   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1852     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1853                                   debug_info);
1854   END IF;
1855 
1856   IF ((p_invoice_rec.vendor_site_id is null) AND
1857       (p_invoice_rec.vendor_site_code is null) AND
1858       (p_vendor_site_id_per_po is null)) THEN
1859 
1860     debug_info := '(Check Invalid Site 2) No Supplier Site, Reject';
1861     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1862       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1863                                     debug_info);
1864     END IF;
1865 
1866     -- no supplier site exists
1867     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1868            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1869             p_invoice_rec.invoice_id,
1870             'NO SUPPLIER SITE',
1871             p_default_last_updated_by,
1872             p_default_last_update_login,
1873             current_calling_sequence) <> TRUE) THEN
1874       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1875         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1876                                       'insert_rejections<-'
1877                                       ||current_calling_sequence);
1878       END IF;
1879       RAISE supplier_site_check_failure;
1880     END IF;
1881 
1882     return_vendor_site_id := null;
1883     l_current_invoice_status := 'N';
1884 
1885   ELSE
1886 
1887     IF p_invoice_rec.vendor_site_id is not null THEN
1888       debug_info := '(Check Invalid Site 3) Get Supplier Site details '
1889                     ||'from p_invoice_rec.vendor_site_id';
1890       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1891         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1892                                       debug_info);
1893       END IF;
1894     /*Bug5503712 Done the code changes so that if vendor site id is not null
1895       CADIP will not reject PPA invoices in following cases.
1896         1.  primary pay site is present  OR
1897         2.  only 1 pay site is present. */
1898       BEGIN
1899         --validate vendor site id
1900         SELECT vendor_site_id, pay_site_flag, terms_date_basis
1901         INTO l_vendor_site_id, l_pay_site_flag, p_terms_date_basis
1902         FROM po_vendor_sites pvs
1903         WHERE vendor_site_id = p_invoice_rec.vendor_site_id
1904          AND nvl(trunc(PVS.INACTIVE_DATE),
1905                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1906              > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1907       EXCEPTION
1908         WHEN no_data_found THEN
1909              BEGIN
1910               --Get Primary Pay site
1911               SELECT vendor_site_id, pay_site_flag, terms_date_basis
1912               INTO l_vendor_site_id, l_pay_site_flag, p_terms_date_basis
1913               FROM po_vendor_sites pvs
1914               WHERE vendor_id = p_invoice_rec.vendor_id
1915               AND   nvl(Primary_pay_site_flag,'N')='Y'
1916               AND   pvs.Org_id=p_invoice_rec.org_id
1917               AND nvl(trunc(PVS.INACTIVE_DATE),
1918                     AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1919                         > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1920 
1921               UPDATE AP_ppa_invoices_gt H
1922                  SET vendor_site_id = l_vendor_site_id
1923                WHERE invoice_id = p_invoice_rec.invoice_id;
1924 
1925 
1926       EXCEPTION
1927         WHEN no_data_found THEN
1928 
1929           BEGIN
1930            --Get pay site id if only one pay site is present
1931            SELECT vendor_site_id, pay_site_flag, terms_date_basis
1932              INTO l_vendor_site_id, l_pay_site_flag, p_terms_date_basis
1933              FROM po_vendor_sites pvs
1934             WHERE vendor_id = p_invoice_rec.vendor_id
1935               AND pvs.Org_id=p_invoice_rec.org_id
1936               AND NVL(pvs.pay_site_flag,'N')='Y'
1937               AND nvl(trunc(PVS.INACTIVE_DATE),
1938                      AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1939                          > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1940 
1941               UPDATE AP_ppa_invoices_gt H
1942                  SET vendor_site_id = l_vendor_site_id
1943                WHERE invoice_id = p_invoice_rec.invoice_id;
1944 
1945           EXCEPTION
1946              WHEN OTHERS THEN
1947         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1948           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
1949             p_invoice_rec.invoice_id,
1950             'INVALID SUPPLIER SITE',
1951             p_default_last_updated_by,
1952             p_default_last_update_login,
1953             current_calling_sequence) <> TRUE) THEN
1954           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1955             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1956                                     'insert_rejections<-'
1957                                     ||current_calling_sequence);
1958           END IF;
1959           RAISE supplier_site_check_failure;
1960         END IF;
1961         return_vendor_site_id := null;
1962         l_current_invoice_status := 'N';
1963       END;
1964      END;
1965     END;
1966 
1967     END IF; -- p_invoice_rec.vendor_site_id is not null
1968 
1969     IF p_invoice_rec.vendor_site_code is not null THEN
1970 
1971       debug_info := '(Check Invalid Site 4) Get Supplier Site details '
1972                    ||'from p_invoice_rec.vendor_site_code';
1973       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
1974         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
1975                                      debug_info);
1976       END IF;
1977 
1978       --validate vendor site code and retrieve vendor site id
1979       BEGIN
1980         SELECT vendor_site_id, pay_site_flag,
1981             terms_date_basis
1982         INTO l_vendor_site_id_per_code, l_pay_site_flag_per_code,
1983             p_terms_date_basis
1984         FROM po_vendor_sites
1985         WHERE vendor_site_code = p_invoice_rec.vendor_site_code
1986         AND vendor_id = p_invoice_rec.vendor_id
1987         AND nvl(trunc(INACTIVE_DATE),AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1)
1988             > AP_IMPORT_INVOICES_PKG.g_inv_sysdate ;
1989        EXCEPTION
1990 
1991         -- Bug 5579196
1992         WHEN too_many_rows THEN
1993           IF p_invoice_rec.org_id is NULL then
1994              NULL;
1995            END IF;
1996 
1997         WHEN no_data_found THEN
1998         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
1999           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2000             p_invoice_rec.invoice_id,
2001             'INVALID SUPPLIER SITE',
2002             p_default_last_updated_by,
2003             p_default_last_update_login,
2004             current_calling_sequence) <> TRUE) THEN
2005           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2006             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2007                                     'insert_rejections<-'
2008                                     ||current_calling_sequence);
2009           END IF;
2010           RAISE supplier_site_check_failure;
2011         END IF;
2012         return_vendor_site_id := null;
2013         l_current_invoice_status := 'N';
2014 
2015       END;
2016 
2017     END IF; -- p_invoice_rec.vendor_site_code is not null
2018 
2019 
2020     IF l_vendor_site_id iS NOT NULL AND
2021       l_vendor_site_id_per_code IS NOT NULL AND
2022       l_vendor_site_id <> l_vendor_site_id_per_code THEN
2023       debug_info :=
2024        '(Check Invalid Site 5) Supplier Site info is inconsistent';
2025       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2026         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2027                                      debug_info);
2028       END IF;
2029 
2030       --vendor site id and vendor site code inconsistent
2031       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2032            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2033             p_invoice_rec.invoice_id,
2034             'INCONSISTENT SUPPL SITE',
2035             p_default_last_updated_by,
2036             p_default_last_update_login,
2037             current_calling_sequence) <> TRUE) THEN
2038          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2039            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2040                                        'insert_rejections<-'
2041                                        ||current_calling_sequence);
2042          END IF;
2043          RAISE supplier_site_check_failure;
2044        END IF;
2045        return_vendor_site_id := null;
2046        l_current_invoice_status := 'N';
2047 
2048      END IF; -- vendor site id is not null, site id from code
2049            -- is not null and they differ
2050 
2051      -- Make sure the vendor site and vendor match
2052      --
2053      IF ((l_vendor_site_id is not null OR
2054        l_vendor_site_id_per_code is not null) AND
2055        p_invoice_rec.vendor_id IS NOT NULL) THEN
2056        debug_info := '(Check Invalid Site 6) Check Supplier Site for'
2057                    ||' given vendor';
2058        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2059           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2060                                      debug_info);
2061        END IF;
2062 
2063        BEGIN
2064          SELECT 'X'
2065          INTO l_valid_vendor
2066          FROM po_vendor_sites
2067          WHERE vendor_site_id = nvl(l_vendor_site_id ,l_vendor_site_id_per_code)
2068          AND vendor_id = p_invoice_rec.vendor_id;
2069 
2070        EXCEPTION
2071          WHEN no_data_found THEN
2072          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2073           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2074             p_invoice_rec.invoice_id,
2075             'INCONSISTENT SUPPL SITE',
2076             p_default_last_updated_by,
2077             p_default_last_update_login,
2078             current_calling_sequence) <> TRUE) THEN
2079             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2080               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2081                                     'insert_rejections<-'
2082                                     ||current_calling_sequence);
2083             END IF;
2084             RAISE supplier_site_check_failure;
2085          END IF;
2086          return_vendor_site_id := null;
2087          l_current_invoice_status := 'N';
2088        END;
2089 
2090        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2091           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2092                    '------------------> l_valid_vendor = '|| l_valid_vendor);
2093        END IF;
2094 
2095      END IF; -- Make sure vendor site and vendor match
2096 
2097      IF l_current_invoice_status = 'Y' THEN
2098      -- Make sure that the EDI site and
2099      -- the PO site belong to the same supplier
2100      -- if not then reject
2101        IF (((l_vendor_site_id is not null) OR
2102           (l_vendor_site_id_per_code is not null)) AND
2103           (p_vendor_site_id_per_po is not null)) THEN
2104 
2105          debug_info := '(Check Invalid Site 7) Check Supplier Site info for EDI'
2106                      ||' and PO site';
2107          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2108            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2109                                        debug_info);
2110          END IF;
2111 
2112          BEGIN
2113            SELECT distinct vendor_id
2114            INTO l_check_vendor_id
2115            FROM po_vendor_sites
2116            WHERE vendor_site_id IN (l_vendor_site_id, p_vendor_site_id_per_po,
2117                 l_vendor_site_id_per_code);
2118 
2119          EXCEPTION
2120            WHEN NO_DATA_FOUND THEN
2121            debug_info := '(Check Invalid Site 8) EDI and PO site are '
2122                          ||'invalid: Reject';
2123            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2124              AP_IMPORT_UTILITIES_PKG.Print(
2125                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2126            END IF;
2127 
2128            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2129                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2130                  p_invoice_rec.invoice_id,
2131                  'INCONSISTENT SUPPL SITE',
2132                  p_default_last_updated_by,
2133                  p_default_last_update_login,
2134                  current_calling_sequence) <> TRUE) THEN
2135              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2136                AP_IMPORT_UTILITIES_PKG.Print(
2137                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
2138                  'insert_rejections<-'||current_calling_sequence);
2139              END IF;
2140              RAISE supplier_site_check_failure;
2141            END IF;
2142 
2143            l_current_invoice_status := 'N';
2144 
2145          WHEN TOO_MANY_ROWS THEN
2146            debug_info := '(Check Invalid Site 9) EDI and PO site are '
2147                          ||'for different supplier';
2148            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2149              AP_IMPORT_UTILITIES_PKG.Print(
2150                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2151            END IF;
2152 
2153            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2154                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2155                  p_invoice_rec.invoice_id,
2156                  'INCONSISTENT SUPPL SITE',
2157                  p_default_last_updated_by,
2158                  p_default_last_update_login,
2159                  current_calling_sequence) <> TRUE) THEN
2160              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2161                AP_IMPORT_UTILITIES_PKG.Print(
2162                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
2163                  'insert_rejections<-' ||current_calling_sequence);
2164              END IF;
2165              RAISE supplier_site_check_failure;
2166            END IF;
2167 
2168            l_current_invoice_status := 'N';
2169 
2170        END;
2171      END IF; -- Do vendor site, vendor site per code and per po
2172              -- belong to same supplier?
2173 
2174      if l_vendor_site_id is null THEN
2175        if nvl(l_pay_site_flag_per_code, 'N') = 'N' THEN
2176          -- pay site is not a pay site
2177          debug_info := '(Check Invalid Site 10) Not a pay site per '
2178                        ||'supplier site code';
2179          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2180            AP_IMPORT_UTILITIES_PKG.Print(
2181              AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2182          END IF;
2183 
2184          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2185               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2186                p_invoice_rec.invoice_id,
2187               'NOT PAY SITE',
2188                p_default_last_updated_by,
2189                p_default_last_update_login,
2190                current_calling_sequence) <> TRUE) THEN
2191            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2192              AP_IMPORT_UTILITIES_PKG.Print(
2193                AP_IMPORT_INVOICES_PKG.g_debug_switch,
2194                'insert_rejections<-' ||current_calling_sequence);
2195            END IF;
2196            RAISE supplier_site_check_failure;
2197          END IF;
2198          l_current_invoice_status := 'N';
2199        END IF; -- Pay site flag per code is N
2200 
2201      ELSE -- Vendor site id is not null
2202        if nvl(l_pay_site_flag, 'N') = 'N' THEN
2203          -- pay site is not a pay site
2204          debug_info := '(Check Invalid Site 11) Not a pay site '
2205                        ||'per supplier site id';
2206          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2207            AP_IMPORT_UTILITIES_PKG.Print(
2208            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
2209          END IF;
2210 
2211          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2212            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2213             p_invoice_rec.invoice_id,
2214             'NOT PAY SITE',
2215             p_default_last_updated_by,
2216             p_default_last_update_login,
2217             current_calling_sequence) <> TRUE) THEN
2218            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2219              AP_IMPORT_UTILITIES_PKG.Print(
2220              AP_IMPORT_INVOICES_PKG.g_debug_switch,
2221              'insert_rejections<-'||current_calling_sequence);
2222            END IF;
2223            RAISE supplier_site_check_failure;
2224          END IF;
2225          l_current_invoice_status := 'N';
2226        END IF; -- vendor site pay site flag is N
2227 
2228      END IF; -- Vendor site id is null
2229 
2230    END IF; -- Make sure site and PO site  belong to the same supplier
2231 
2232    -- if all checks passed successfully, save vendor_site_id
2233    if l_current_invoice_status = 'Y' THEN
2234      if l_vendor_site_id is null THEN
2235        return_vendor_site_id := l_vendor_site_id_per_code;
2236      else
2237        return_vendor_site_id := l_vendor_site_id;
2238      end if;
2239    end if;
2240 
2241  END IF; -- p_invoice_rec.vendor_site_id is null
2242          -- p_invoice_rec.vendor_site_code is null AND
2243          -- p_vendor_site_id_per_po is null
2244 
2245  p_return_vendor_site_id := return_vendor_site_id;
2246  p_current_invoice_status := l_current_invoice_status;
2247  RETURN (TRUE);
2248 
2249 EXCEPTION
2250   WHEN no_data_found THEN
2251     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2252           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2253             p_invoice_rec.invoice_id,
2254             'INVALID SUPPLIER SITE',
2255             p_default_last_updated_by,
2256             p_default_last_update_login,
2257             current_calling_sequence) <> TRUE) THEN
2258       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2259         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2260                                     'insert_rejections<-'
2261                                     ||current_calling_sequence);
2262       END IF;
2263       RAISE supplier_site_check_failure;
2264     END IF;
2265 
2266     l_current_invoice_status := 'N';
2267 
2268     p_return_vendor_site_id := return_vendor_site_id;
2269     p_current_invoice_status := l_current_invoice_status;
2270     RETURN (TRUE);
2271 
2272   WHEN OTHERS THEN
2273     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2274       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2275                                     debug_info);
2276     END IF;
2277 
2278     IF (SQLCODE < 0) then
2279       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2280         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2281                                       SQLERRM);
2282       END IF;
2283     END IF;
2284     RETURN (FALSE);
2285 
2286 END v_check_invalid_supplier_site;
2287 
2288 
2289 
2290 -----------------------------------------------------------------------------
2291 -- This function is used to perform Party validation
2292 --
2293 -----------------------------------------------------------------------------
2294 FUNCTION v_check_invalid_party(
2295          p_invoice_rec   IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2296          p_default_last_updated_by     IN            NUMBER,
2297          p_default_last_update_login   IN            NUMBER,
2298          p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
2299          p_calling_sequence            IN            VARCHAR2)
2300 RETURN BOOLEAN IS
2301 
2302 party_check_failure         EXCEPTION;
2303 l_party_id                  NUMBER;
2304 l_current_invoice_status    VARCHAR2(1) := 'Y';
2305 current_calling_sequence    VARCHAR2(2000);
2306 debug_info                  VARCHAR2(500);
2307 
2308 
2309 BEGIN
2310   -- Update the calling sequence
2311   --
2312   current_calling_sequence :=
2313     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_party<-'
2314     ||P_calling_sequence;
2315 
2316   IF (p_invoice_rec.party_id is NULL) THEN
2317 
2318     -------------------------------------------------------------------------
2319     -- Step 1
2320     -- Check for Null Party.
2321     -------------------------------------------------------------------------
2322     debug_info := '(Check Invalid Party 1) Check for Null Party.';
2323     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2324       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2325                                     debug_info);
2326     END IF;
2327 
2328     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2329             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2330              p_invoice_rec.invoice_id,
2331              'INVALID PARTY',
2332              p_default_last_updated_by,
2333              p_default_last_update_login,
2334              current_calling_sequence) <> TRUE) THEN
2335       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2336         AP_IMPORT_UTILITIES_PKG.Print(
2337           AP_IMPORT_INVOICES_PKG.g_debug_switch,
2338           'insert_rejections<-'||current_calling_sequence);
2339       END IF;
2340       RAISE party_check_failure;
2341     END IF;
2342 
2343   ELSE
2344 
2345      IF (p_invoice_rec.party_id is NOT NULL) THEN
2346        ----------------------------------------------------------------------
2347        -- Step 2
2348        -- validate party id
2349        ----------------------------------------------------------------------
2350        debug_info := '(Check Invalid Party 2) Validate party id.';
2351        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2352          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2353                                        debug_info);
2354        END IF;
2355 
2356        SELECT party_id
2357          INTO l_party_id
2358          FROM hz_parties hzp
2359         WHERE party_id = p_invoice_rec.party_id;
2360 
2361      END IF;
2362 
2363   END IF;
2364 
2365   p_current_invoice_status := l_current_invoice_status;
2366   RETURN (TRUE);
2367 
2368 EXCEPTION
2369   WHEN no_data_found THEN
2370 
2371     -------------------------------------------------------------------------
2372     -- Step 8
2373     -- Check for invalid Party.
2374     -------------------------------------------------------------------------
2375     debug_info := '(Check Invalid Party 8) Check for invalid Party.';
2376     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2377       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2378                                     debug_info);
2379     END IF;
2380 
2381     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2382                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2383                 p_invoice_rec.invoice_id,
2384                 'INVALID PARTY',
2385                 p_default_last_updated_by,
2386                 p_default_last_update_login,
2387                 current_calling_sequence) <> TRUE) THEN
2388       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2389         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2390           'insert_rejections<-'||current_calling_sequence);
2391       END IF;
2392       RAISE party_check_failure;
2393 
2394     END IF;
2395     l_current_invoice_status := 'N';
2396     p_current_invoice_status := l_current_invoice_status;
2397     RETURN (TRUE);
2398 
2399 
2400   WHEN OTHERS THEN
2401     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2402       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2403                                     debug_info);
2404     END IF;
2405 
2406     IF (SQLCODE < 0) then
2407       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2408         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2409                                       SQLERRM);
2410       END IF;
2411     END IF;
2412     RETURN(FALSE);
2413 
2414 END v_check_invalid_party;
2415 
2416 
2417 
2418 ------------------------------------------------------------------
2419 -- This function is used to perform Party Site validation
2420 --
2421 ------------------------------------------------------------------
2422 FUNCTION v_check_invalid_party_site (
2423          p_invoice_rec  IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2424          p_default_last_updated_by    IN            NUMBER,
2425          p_default_last_update_login  IN            NUMBER,
2426          p_return_party_site_id       OUT NOCOPY    NUMBER,
2427          p_terms_date_basis           OUT NOCOPY    VARCHAR2,
2428          p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
2429          p_calling_sequence           IN            VARCHAR2)
2430 RETURN BOOLEAN IS
2431 
2432 party_site_check_failure        EXCEPTION;
2433 l_party_site_id                 NUMBER(15);
2434 l_current_invoice_status        VARCHAR2(1):='Y';
2435 return_party_site_id            NUMBER(15);
2436 current_calling_sequence        VARCHAR2(2000);
2437 debug_info                      VARCHAR2(500);
2438 
2439 BEGIN
2440   -- Update the calling sequence
2441   --
2442   current_calling_sequence :=
2443     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_party_site<-'
2444      ||P_calling_sequence;
2445 
2446   debug_info := '(Check Invalid Party Site 1) Check Party Site';
2447   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2448     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2449                                   debug_info);
2450   END IF;
2451 
2452   IF (p_invoice_rec.party_site_id is null) THEN
2453 
2454       BEGIN
2455         SELECT party_site_id
2456         INTO   l_party_site_id
2457         FROM   HZ_Party_Sites HPS
2458         WHERE  HPS.Party_ID = p_invoice_rec.party_id
2459         AND    HPS.Identifying_Address_Flag = 'Y'
2460         AND    NVL(HPS.Start_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2461                          <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
2462         AND    NVL(HPS.End_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2463                          >= AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
2464 
2465       EXCEPTION
2466         when no_data_found then
2467              debug_info := '(Check Invalid Party Site 2) No Party Site, Reject';
2468 
2469              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2470                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2471                                        debug_info);
2472              END IF;
2473 
2474              -- no party site exists
2475              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2476                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2477                       p_invoice_rec.invoice_id,
2478                       'INVALID PARTY SITE',
2479                       p_default_last_updated_by,
2480                       p_default_last_update_login,
2481                       current_calling_sequence) <> TRUE) THEN
2482                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2483                        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2484                                        'insert_rejections<-'
2485                                        ||current_calling_sequence);
2486                    END IF;
2487                    RAISE party_site_check_failure;
2488              END IF;
2489              l_current_invoice_status := 'N';
2490        END;
2491 
2492   ELSE
2493 
2494       debug_info := '(Check Invalid Party Site 3) Check Party Site ';
2495       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2496         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2497                                       debug_info);
2498       END IF;
2499 
2500       BEGIN
2501         --validate party site id
2502         SELECT party_site_id
2503         INTO   l_party_site_id
2504         FROM   hz_party_sites hps
2505         WHERE  party_site_id = p_invoice_rec.party_site_id
2506         AND    party_id = p_invoice_rec.party_id
2507         AND    status = 'A'
2508         AND    NVL(HPS.Start_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2509                          <= AP_IMPORT_INVOICES_PKG.g_inv_sysdate
2510         AND    NVL(HPS.End_Date_Active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate)
2511                          >= AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
2512 
2513       EXCEPTION
2514         when no_data_found then
2515              debug_info := '(Check Invalid Party Site 2) Invalid Party Site, Reject';
2516              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2517                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2518                                        debug_info);
2519              END IF;
2520 
2521              -- invalid party site
2522              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2523                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2524                       p_invoice_rec.invoice_id,
2525                       'INVALID PARTY SITE',
2526                       p_default_last_updated_by,
2527                       p_default_last_update_login,
2528                       current_calling_sequence) <> TRUE) THEN
2529                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2530                        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2531                                        'insert_rejections<-'
2532                                        ||current_calling_sequence);
2533                    END IF;
2534                    RAISE party_site_check_failure;
2535              END IF;
2536              l_current_invoice_status := 'N';
2537        END;
2538 
2539     END IF;
2540 
2541 
2542     -- Get terms_date_basis from ap_system_parameters
2543     SELECT terms_date_basis
2544     INTO   p_terms_date_basis
2545     FROM   ap_system_parameters
2546     WHERE  org_id = p_invoice_rec.org_id;
2547 
2548 
2549     -- if all checks passed successfully, save party_site_id
2550     if l_current_invoice_status = 'Y' THEN
2551        return_party_site_id := l_party_site_id;
2552     end if;
2553 
2554 
2555   p_return_party_site_id := return_party_site_id;
2556   p_current_invoice_status := l_current_invoice_status;
2557   RETURN (TRUE);
2558 
2559 EXCEPTION
2560 
2561   WHEN OTHERS THEN
2562     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2563         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2564                                       debug_info);
2565     END IF;
2566 
2567     IF (SQLCODE < 0) then
2568       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2569           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2570                                        SQLERRM);
2571       END IF;
2572     END IF;
2573     RETURN (FALSE);
2574 
2575 END v_check_invalid_party_site;
2576 
2577 
2578 ------------------------------------------------------------------------------
2579 -- This function is used to validate that the invoice num is
2580 -- neither null, nor a duplicate of an existing or interface
2581 -- invoice.
2582 --
2583 -----------------------------------------------------------------------------
2584 FUNCTION v_check_invalid_invoice_num (
2585    p_invoice_rec                 IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2586    p_allow_interest_invoices     IN VARCHAR2,   --Bug4113223
2587    p_invoice_num                    OUT NOCOPY VARCHAR2,
2588    p_default_last_updated_by     IN            NUMBER,
2589    p_default_last_update_login   IN            NUMBER,
2590    p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
2591    p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
2592 IS
2593 
2594 invoice_num_check_failure    EXCEPTION;
2595 l_invoice_count              NUMBER;
2596 l_count_in_history_invoices  NUMBER;
2597 l_invoice_num                AP_INVOICES.INVOICE_NUM%TYPE;
2598 l_current_invoice_status     VARCHAR2(1) := 'Y';
2599 current_calling_sequence     VARCHAR2(2000);
2600 debug_info                   VARCHAR2(500);
2601 
2602 BEGIN
2603   -- Update the calling sequence
2604   --
2605   current_calling_sequence :=
2606     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_invoice_num<-'
2607     ||P_calling_sequence;
2608 
2609   IF (p_invoice_rec.invoice_num IS NULL) Then
2610     l_invoice_num := to_char(nvl(p_invoice_rec.invoice_date,
2611                                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate),
2612                              'DD/MM/RR');
2613   ELSE
2614     l_invoice_num := p_invoice_rec.invoice_num;
2615   End If;
2616 
2617 
2618   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2619     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2620                         '------------------> l_invoice_num  =
2621                         '||l_invoice_num);
2622   END IF;
2623 
2624   IF (l_invoice_num is NULL) THEN
2625 
2626      ------------------------------------------------------------------------
2627      -- Step 1
2628      -- Check for NULL Invoice NUMBER.
2629      -- This should never happen
2630      ------------------------------------------------------------------------
2631      debug_info := '(Check Invoice Number 1) Check for Null Invoice Number.';
2632      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2633        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2634                                      debug_info);
2635      END IF;
2636 
2637      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2638           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2639             p_invoice_rec.invoice_id,
2640             'NO INVOICE NUMBER',
2641             p_default_last_updated_by,
2642             p_default_last_update_login,
2643             current_calling_sequence) <> TRUE) THEN
2644        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2645          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2646                                        'insert_rejections<-'
2647                                        ||current_calling_sequence);
2648        END IF;
2649        RAISE invoice_num_check_failure;
2650      END IF;
2651 
2652      l_current_invoice_status := 'N';
2653 
2654   ELSE
2655      ------------------------------------------------------------------------
2656      -- Step 2
2657      -- Check for Invalid Invoice NUMBER.
2658      ------------------------------------------------------------------------
2659 
2660      /* Bugfix: 4113223
2661      Raise an exception if the invoice number has more than 45 characters
2662      and interest invoices option is enabled*/
2663 
2664      debug_info := '(Check Invoice Number 2) Check for Invalid Invoice Number.';
2665      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2666        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2667                                      debug_info);
2668      END IF;
2669 
2670      IF (nvl(p_allow_interest_invoices,'N') = 'Y'
2671          AND LENGTH(l_invoice_num) > 45) THEN
2672 
2673 	IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2674                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2675                         p_invoice_rec.invoice_id,
2676                         'INVALID INVOICE NUMBER',
2677                         p_default_last_updated_by,
2678                         p_default_last_update_login,
2679                         current_calling_sequence,
2680                         'Y',
2681                         'INVOICE NUMBER',
2682                         l_invoice_num) <> TRUE) THEN
2683          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2684            AP_IMPORT_UTILITIES_PKG.Print(
2685              AP_IMPORT_INVOICES_PKG.g_debug_switch,
2686              'insert_rejections<-'||current_calling_sequence);
2687          END IF;
2688          RAISE invoice_num_check_failure;
2689        END IF;
2690 
2691        l_current_invoice_status := 'N';
2692 
2693      END IF;
2694 
2695      ------------------------------------------------------------------------
2696      -- Step 3
2697      -- Check for Duplicate Invoice NUMBER.
2698      ------------------------------------------------------------------------
2699      debug_info := '(Check Invoice Number 3) Check for Duplicate '
2700                    ||'Invoice Number.';
2701      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2702        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2703                                      debug_info);
2704      END IF;
2705 
2706      SELECT count(*)
2707       INTO  l_invoice_count
2708       FROM  ap_invoices
2709      WHERE  vendor_id = p_invoice_rec.vendor_id
2710        AND  invoice_num = l_invoice_num
2711        AND  rownum = 1;
2712 
2713 
2714      SELECT count(*)
2715        INTO l_count_in_history_invoices
2716        FROM ap_history_invoices
2717       WHERE vendor_id = p_invoice_rec.vendor_id
2718         AND invoice_num = l_invoice_num;
2719 
2720 
2721      IF ((l_invoice_count > 0) OR (l_count_in_history_invoices > 0)) THEN
2722 
2723        -- Pass context for XML GATEWAY
2724        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2725                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2726                         p_invoice_rec.invoice_id,
2727                         'DUPLICATE INVOICE NUMBER',
2728                         p_default_last_updated_by,
2729                         p_default_last_update_login,
2730                         current_calling_sequence,
2731                         'Y',
2732                         'INVOICE NUMBER',
2733                         l_invoice_num) <> TRUE) THEN
2734          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2735            AP_IMPORT_UTILITIES_PKG.Print(
2736              AP_IMPORT_INVOICES_PKG.g_debug_switch,
2737              'insert_rejections<-'||current_calling_sequence);
2738          END IF;
2739          RAISE invoice_num_check_failure;
2740        END IF;
2741 
2742        l_current_invoice_status := 'N';
2743 
2744      END IF;
2745   END IF;
2746 
2747   p_current_invoice_status := l_current_invoice_status;
2748   p_invoice_num := l_invoice_num;
2749   RETURN (TRUE);
2750 
2751 EXCEPTION
2752   WHEN OTHERS THEN
2753     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2754       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2755                                     debug_info);
2756     END IF;
2757 
2758     IF (SQLCODE < 0) then
2759       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2760         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2761                                       SQLERRM);
2762       END IF;
2763     END IF;
2764     RETURN(FALSE);
2765 
2766 END v_check_invalid_invoice_num;
2767 
2768 
2769 ------------------------------------------------------------------
2770 -- This function is used to validate that the invoice currency code
2771 -- is neither inactive, nor invalid.
2772 --
2773 ------------------------------------------------------------------
2774 FUNCTION v_check_invalid_inv_curr_code (
2775            p_invoice_rec IN    AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2776            p_inv_currency_code            OUT NOCOPY VARCHAR2,
2777            p_min_acc_unit_inv_curr        OUT NOCOPY NUMBER,
2778            p_precision_inv_curr           OUT NOCOPY NUMBER,
2779            p_default_last_updated_by   IN            NUMBER,
2780            p_default_last_update_login IN            NUMBER,
2781            p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
2782            p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
2783 IS
2784 
2785 invalid_inv_curr_code_failure  EXCEPTION;
2786 l_current_invoice_status       VARCHAR2(1) := 'Y';
2787 l_start_date_active            DATE;
2788 l_end_date_active              DATE;
2789 current_calling_sequence       VARCHAR2(2000);
2790 debug_info                     VARCHAR2(500);
2791 l_min_acc_unit_inv_curr        fnd_currencies.minimum_accountable_unit%TYPE;
2792 l_precision_inv_curr           fnd_currencies.precision%TYPE;
2793 l_enabled_flag                 fnd_currencies.enabled_flag%TYPE;
2794 
2795 l_valid_inv_currency           fnd_currencies.currency_code%TYPE;
2796 
2797 BEGIN
2798   -- Update the calling sequence
2799   --
2800   current_calling_sequence :=
2801     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_inv_curr_code<-'
2802     ||P_calling_sequence;
2803 
2804   p_inv_currency_code := p_invoice_rec.invoice_currency_code;
2805 
2806 
2807   --------------------------------------------------------------------------
2808   -- Step 1
2809   -- If Invoice Currency Code is null ,default from PO Vendor Sites
2810   --------------------------------------------------------------------------
2811   IF (p_invoice_rec.invoice_currency_code IS NULL) Then
2812     debug_info := '(Check Invoice Currency Code 1) Invoice Currency Code is '
2813                   ||'null ,default from PO Vendor Sites.';
2814     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2815       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2816                                     debug_info);
2817     END IF;
2818 
2819     -- Added for payment requests project
2820     IF (p_invoice_rec.party_site_id IS NOT NULL) THEN
2821         -- If No curr code in vendor site ,then the default exception
2822         -- will reject.
2823         SELECT Invoice_currency_code
2824           INTO p_inv_currency_code
2825           FROM AP_System_Parameters
2826          WHERE Org_ID = p_invoice_rec.org_id;
2827 
2828     ELSE
2829         -- If No curr code in vendor site ,then the default exception
2830         -- will reject.
2831         SELECT Invoice_currency_code
2832           INTO p_inv_currency_code
2833           FROM po_vendor_sites
2834          WHERE vendor_site_id = p_invoice_rec.vendor_site_id;
2835     END IF;
2836 
2837   END IF;
2838 
2839   --------------------------------------------------------------------------
2840   -- Step 2
2841   -- Get the state of the invoice currency and precision and mau
2842   --------------------------------------------------------------------------
2843   debug_info := '(Check Invoice Currency Code 2) Get precision, '
2844                 ||'mau for Invoice Currency Code.';
2845   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2846     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2847                                   debug_info);
2848   END IF;
2849 
2850   /*SELECT start_date_active, end_date_active,
2851          minimum_accountable_unit, precision, enabled_flag
2852     INTO l_start_date_active, l_end_date_active,
2853          l_min_acc_unit_inv_curr,l_precision_inv_curr, l_enabled_flag
2854     FROM fnd_currencies
2855    WHERE currency_code = p_inv_currency_code; */
2856 
2857    -- Bug 5448579
2858   FOR i IN AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab.First..AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab.Last
2859   LOOP
2860     IF AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).currency_code = p_inv_currency_code THEN
2861         l_valid_inv_currency  := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).currency_code;
2862         l_start_date_active   := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).start_date_active;
2863         l_end_date_active     := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).end_date_active;
2864         l_min_acc_unit_inv_curr := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).minimum_accountable_unit;
2865         l_precision_inv_curr  := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).precision;
2866         l_enabled_flag        := AP_IMPORT_INVOICES_PKG.g_fnd_currency_tab(i).enabled_flag;
2867       EXIT;
2868     END IF;
2869   END LOOP;
2870 
2871   debug_info := 'l_valid_inv_currency: '||l_valid_inv_currency;
2872   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2873     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2874                                     debug_info);
2875   END IF;
2876 
2877 
2878   p_min_acc_unit_inv_curr := l_min_acc_unit_inv_curr;
2879   p_precision_inv_curr := l_precision_inv_curr;
2880 
2881   IF ((trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate) <
2882        nvl(l_start_date_active,
2883            trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate))) OR
2884       (AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
2885        nvl(l_end_date_active,
2886            AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))) OR
2887       l_enabled_flag <> 'Y' THEN
2888 
2889     -------------------------------------------------------------------------
2890     -- Step 3
2891     -- Check for Inactive Invoice Currency Code.
2892     -------------------------------------------------------------------------
2893     debug_info := '(Check Invoice Currency Code 3) Check for Inactive Invoice'
2894                   ||' Currency Code.';
2895     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2896       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2897                                     debug_info);
2898     END IF;
2899 
2900     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2901           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2902             p_invoice_rec.invoice_id,
2903             'INACTIVE CURRENCY CODE',
2904             p_default_last_updated_by,
2905             p_default_last_update_login,
2906             current_calling_sequence) <> TRUE) THEN
2907       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2908         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2909                             'insert_rejections<-'||current_calling_sequence);
2910       END IF;
2911       RAISE invalid_inv_curr_code_failure;
2912     END IF;
2913 
2914     l_current_invoice_status := 'N';
2915   END IF;
2916 
2917   p_current_invoice_status := l_current_invoice_status;
2918   RETURN (TRUE);
2919 
2920 EXCEPTION
2921   WHEN no_data_found THEN
2922 
2923     --------------------------------------------------------------------------
2924     -- Step 4
2925     -- Check for Invalid Invoice Currency Code.
2926     --------------------------------------------------------------------------
2927     debug_info := '(Check Invoice Currency Code 4) Check for Invalid Invoice '
2928                   ||'Currency Code.';
2929     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2930       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2931                                     debug_info);
2932     END IF;
2933 
2934     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
2935           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
2936             p_invoice_rec.invoice_id,
2937             'INVALID CURRENCY CODE',
2938             p_default_last_updated_by,
2939             p_default_last_update_login,
2940             current_calling_sequence) <> TRUE) THEN
2941       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2942         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2943         'insert_rejections<-'||current_calling_sequence);
2944       END IF;
2945       RAISE invalid_inv_curr_code_failure;
2946     END IF;
2947 
2948     l_current_invoice_status := 'N';
2949     p_current_invoice_status := l_current_invoice_status;
2950     RETURN (TRUE);
2951 
2952   WHEN OTHERS THEN
2953     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2954       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2955                                     debug_info);
2956     END IF;
2957 
2958     IF (SQLCODE < 0) then
2959       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
2960         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
2961                                       SQLERRM);
2962       END IF;
2963     END IF;
2964     RETURN(FALSE);
2965 
2966 END v_check_invalid_inv_curr_code;
2967 
2968 
2969 ------------------------------------------------------------------------------
2970 -- This function is used to validate that the invoice type and
2971 -- amount are appropriate.  It also reads the invoice type if
2972 -- null and also sets the match mode based on invoice type.
2973 --
2974 ------------------------------------------------------------------------------
2975 FUNCTION v_check_invoice_type_amount (
2976          p_invoice_rec               IN
2977           AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
2978          p_invoice_type_lookup_code     OUT NOCOPY VARCHAR2,
2979          p_match_mode                   OUT NOCOPY VARCHAR2,
2980          p_precision_inv_curr        IN            NUMBER,
2981          p_default_last_updated_by   IN            NUMBER,
2982          p_default_last_update_login IN            NUMBER,
2983          p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
2984          p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
2985 IS
2986 
2987 invalid_type_lookup_failure    EXCEPTION;
2988 l_current_invoice_status       VARCHAR2(1) := 'Y';
2989 l_lines_amount_sum             NUMBER := 0;
2990 l_no_of_lines                  NUMBER := 0;
2991 current_calling_sequence       VARCHAR2(2000);
2992 debug_info                     VARCHAR2(500);
2993 
2994 BEGIN
2995   -- Update the calling sequence
2996   --
2997   current_calling_sequence :=
2998     'AP_IMPORT_INVOICES_PKG.v_check_invoice_type_amount<-'
2999     ||P_calling_sequence;
3000 
3001   --------------------------------------------------------------------------
3002   -- Step 1
3003   -- Check for Invalid Invoice type lookup code.
3004   --------------------------------------------------------------------------
3005   debug_info := '(Check Invoice Type and Amount 1) Check for Invalid Invoice'
3006                 ||' type lookup code.';
3007   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3008     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3009                                   debug_info);
3010   END IF;
3011 
3012   p_invoice_type_lookup_code := p_invoice_rec.invoice_type_lookup_code;
3013 
3014   -- We only support importing invoice types 'STANDARD', 'CREDIT',
3015   -- 'PREPAYMENT'  -- Contract Payments
3016   -- and 'PO PRICE ADJUST' --Retropricing
3017   -- and 'DEBIT' -- Debit Memo
3018   -- Also we check for invalid lookup code only if it is not null
3019   -- Else we populate STANDARD for invoice amount >=0 and CREDIT for
3020   -- invoice amount <0
3021 
3022   --Bug 4410499 Added EXPENSE REPORT  to the list of
3023   --invoice types we support thru open interface import
3024 
3025   --Contract Payments : Added 'PREPAYMENT' to the IF condition.
3026   --Payment Requests : Added 'PAYMENT REQUEST' to the IF condition
3027   --Bug 7299826 EC Subcon Project : Added 'DEBIT' to the IF condition
3028   IF ((p_invoice_rec.invoice_type_lookup_code IS NOT NULL) AND
3029      (p_invoice_rec.invoice_type_lookup_code NOT IN (
3030                   'STANDARD','CREDIT', 'DEBIT', 'PO PRICE ADJUST','PREPAYMENT','EXPENSE REPORT',
3031                   'PAYMENT REQUEST')))
3032     THEN
3033 
3034     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3035           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3036             p_invoice_rec.invoice_id,
3037             'INVALID INV TYPE LOOKUP',
3038             p_default_last_updated_by,
3039             p_default_last_update_login,
3040             current_calling_sequence) <> TRUE) THEN
3041       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3042         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3043         'insert_rejections<-'||current_calling_sequence);
3044       END IF;
3045       RAISE invalid_type_lookup_failure;
3046     END IF;
3047 
3048     l_current_invoice_status := 'N';
3049 
3050   ELSIF ((p_invoice_rec.invoice_type_lookup_code IS NULL) AND
3051          (p_invoice_rec.invoice_amount >=0)) THEN
3052 
3053     debug_info := '(Check Invoice Type and Amount 2) Invoice type lookup '
3054                   ||'code is null, setting to STANDARD.';
3055     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3056       AP_IMPORT_UTILITIES_PKG.Print(
3057       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
3058     END IF;
3059 
3060     p_invoice_type_lookup_code := 'STANDARD';
3061 
3062   ELSIF ((p_invoice_rec.invoice_type_lookup_code IS NULL) AND
3063          (p_invoice_rec.invoice_amount < 0)) THEN
3064 
3065     debug_info := '(Check Invoice Type and Amount 2) Invoice type lookup '
3066                   ||'code is null, setting to CREDIT.';
3067     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3068       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3069                                     debug_info);
3070     END IF;
3071 
3072     p_invoice_type_lookup_code := 'CREDIT';
3073 
3074   END IF;
3075 
3076   --------------------------------------------------------------------------
3077   -- Step 2
3078   -- Check for Null Invoice Amount.
3079   --------------------------------------------------------------------------
3080   debug_info := '(Check Invoice Type and Amount 2) Check for Null Invoice'
3081                 ||' amount.';
3082   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3083     AP_IMPORT_UTILITIES_PKG.Print(
3084     AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3085   END IF;
3086 
3087   IF (p_invoice_rec.invoice_amount IS NULL) THEN
3088 
3089     -- Set contextual information for XML GATEWAY
3090     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3091                          (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3092                           p_invoice_rec.invoice_id,
3093                           'INVALID INVOICE AMOUNT',
3094                           p_default_last_updated_by,
3095                           p_default_last_update_login,
3096                           current_calling_sequence,
3097                           'Y') <> TRUE) THEN
3098       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3099         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3100         'insert_rejections<-'||current_calling_sequence);
3101       END IF;
3102       RAISE invalid_type_lookup_failure;
3103     END IF;
3104 
3105     l_current_invoice_status := 'N';
3106 
3107   ELSE
3108 
3109     --------------------------------------------------------------------------
3110     -- Step 3
3111     -- Check for Invalid Invoice amount.
3112     --------------------------------------------------------------------------
3113     debug_info := '(Check Invoice Type and Amount 3) Check for Invalid '
3114                   ||'Invoice amount.';
3115     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3116       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3117                                     debug_info);
3118     END IF;
3119 
3120     --Contract Payments: Modified the IF condition to add 'Prepayment' type
3121     --Payment Requests: Added 'PAYMENT REQUEST' type to the IF condition
3122     IF (((nvl(p_invoice_type_lookup_code,'DUMMY')
3123                     IN ('Standard','STANDARD','Prepayment','PREPAYMENT'/*, -- Bug 7002267
3124                         'PAYMENT REQUEST'*/)) AND
3125                        (p_invoice_rec.invoice_amount < 0))  OR
3126        ((nvl(p_invoice_type_lookup_code,'DUMMY') IN ('CREDIT', 'DEBIT')) AND --Bug 7299826 - Added DEBIT
3127           (p_invoice_rec.invoice_amount > 0))) THEN        -- Bug 2822878
3128 
3129       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3130            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3131             p_invoice_rec.invoice_id,
3132             'INCONSISTENT INV TYPE/AMT',
3133             p_default_last_updated_by,
3134             p_default_last_update_login,
3135             current_calling_sequence) <> TRUE) THEN
3136         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3137           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3138           'insert_rejections<-'||current_calling_sequence);
3139         END IF;
3140         RAISE invalid_type_lookup_failure;
3141       END IF;
3142       l_current_invoice_status := 'N';
3143     END IF;
3144 
3145     --------------------------------------------------------------------------
3146     -- Step 4
3147     -- Check for Invoice amount to match sum of invoice lines amount.
3148     -- Also check that number of lines is not 0.
3149     -- The amount check will only be done for EDI GATEWAY invoices since all
3150     -- other type of invoices should go through as they would in the Invoice
3151     -- Workbench. Specifically, this change came about due to the need to have
3152     -- ERS invoices entered with lines exclusive of tax and no tax line in
3153     -- which case the invoice amount will not total the sum of the lines.
3154     -- The tax is then calculated through either calculate tax in the invoice
3155     -- workbench or approval.  In any case, if the total of the lines does
3156     -- not equal the invoice total the invoice would go on hold.
3157     -------------------------------------------------------------------------
3158     --Retropricing
3159     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
3160         debug_info := '(Check Invoice Type and Amount 4) Check for Invoice amount'
3161                       ||' to match sum of invoice line amounts.';
3162         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3163           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3164                                         debug_info);
3165         END IF;
3166 
3167         SELECT nvl(sum(amount),0) , count(*)
3168           INTO l_lines_amount_sum, l_no_of_lines
3169           FROM ap_invoice_lines_interface
3170          WHERE invoice_id = p_invoice_rec.invoice_id;
3171 
3172         IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') THEN
3173           debug_info := '(Check Invoice step 4) Check Invoice amount to match '
3174                         ||'sum of invoice line amounts for EDI only.';
3175           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3176             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3177                                           debug_info);
3178           END IF;
3179 
3180           IF (l_lines_amount_sum <> p_invoice_rec.invoice_amount) THEN
3181 
3182             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3183                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3184                 p_invoice_rec.invoice_id,
3185                 'INVOICE AMOUNT INCORRECT',
3186                 p_default_last_updated_by,
3187                 p_default_last_update_login,
3188                 current_calling_sequence) <> TRUE) THEN
3189               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3190                 AP_IMPORT_UTILITIES_PKG.Print(
3191                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
3192                 'insert_rejections<-'||current_calling_sequence);
3193               END IF;
3194               RAISE invalid_type_lookup_failure;
3195             END IF;
3196             l_current_invoice_status := 'N';
3197           END IF;
3198         END IF; -- Source EDI GATEWAY
3199 
3200         IF (l_no_of_lines = 0) THEN
3201           debug_info := '(Check Invoice Type and Amount 4) No Lines for this '
3202                         ||'invoice.';
3203           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3204             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3205                                           debug_info);
3206           END IF;
3207 
3208           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3209               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3210                 p_invoice_rec.invoice_id,
3211                 'NO INVOICE LINES',
3212                 p_default_last_updated_by,
3213                 p_default_last_update_login,
3214                 current_calling_sequence) <> TRUE) THEN
3215             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3216               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3217               'insert_rejections<-'||current_calling_sequence);
3218             END IF;
3219             RAISE invalid_type_lookup_failure;
3220           END IF;
3221           l_current_invoice_status := 'N';
3222         END IF; -- No of lines is 0
3223     END IF; --source <> PPA
3224 
3225     --------------------------------------------------------------------------
3226     -- Step 5
3227     -- Check for appropriate formatting of the invoice amount.
3228     --------------------------------------------------------------------------
3229     IF LENGTH((ABS(p_invoice_rec.invoice_amount) -
3230                  TRUNC(ABS(p_invoice_rec.invoice_amount)))) - 1
3231                > NVL(p_precision_inv_curr,0) THEN
3232       debug_info := '(Check Invoice Type and Amount 5) Invoice or Lines '
3233                     ||'amount exceeds precision.';
3234       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3235         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3236                                       debug_info);
3237       END IF;
3238 
3239       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3240                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3241                         p_invoice_rec.invoice_id,
3242                         'AMOUNT EXCEEDS PRECISION',
3243                         p_default_last_updated_by,
3244                         p_default_last_update_login,
3245                         current_calling_sequence) <> TRUE) THEN
3246         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3247           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3248           'insert_rejections<-'||current_calling_sequence);
3249         END IF;
3250         RAISE invalid_type_lookup_failure;
3251       END IF;
3252       l_current_invoice_status := 'N';
3253     END IF; -- Precision exceeded
3254 
3255   END IF; -- Invoice amount is null
3256 
3257   --------------------------------------------------------------------------
3258   -- Step 6
3259   -- Determine match mode.
3260   --------------------------------------------------------------------------
3261   debug_info := '(Check Invoice Type and Amount 6) Determine Match Mode.';
3262   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3263     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3264                                   debug_info);
3265   END IF;
3266 
3267   If (p_invoice_type_lookup_code = 'PO PRICE ADJUST') Then
3268 
3269       p_match_mode := 'PO PRICE ADJUSTMENT';
3270 
3271   End If;
3272 
3273   p_current_invoice_status := l_current_invoice_status;
3274   RETURN (TRUE);
3275 
3276 EXCEPTION
3277   WHEN OTHERS THEN
3278     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3279       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3280                                     debug_info);
3281     END IF;
3282 
3283     IF (SQLCODE < 0) then
3284       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3285         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3286                                       SQLERRM);
3287       END IF;
3288     END IF;
3289   RETURN(FALSE);
3290 
3291 END v_check_invoice_type_amount;
3292 
3293 
3294 ----------------------------------------------------------------------------
3295 -- This function is used to validate that the awt information
3296 -- is valid and consistent.
3297 --
3298 ----------------------------------------------------------------------------
3299 FUNCTION v_check_invalid_awt_group (
3300     p_invoice_rec        IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3301     p_awt_group_id                  OUT NOCOPY NUMBER,
3302     p_default_last_updated_by    IN            NUMBER,
3303     p_default_last_update_login  IN            NUMBER,
3304     p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
3305     p_calling_sequence           IN            VARCHAR2) RETURN BOOLEAN
3306 IS
3307 
3308 awt_group_check_failure     EXCEPTION;
3309 l_current_invoice_status    VARCHAR2(1) := 'Y';
3310 l_awt_group_id              AP_INVOICES.AWT_GROUP_ID%TYPE;
3311 l_awt_group_id_per_name     AP_INVOICES.AWT_GROUP_ID%TYPE;
3312 l_inactive_date             DATE;
3313 l_inactive_date_per_name    DATE;
3314 current_calling_sequence    VARCHAR2(2000);
3315 debug_info                  VARCHAR2(500);
3316 
3317 BEGIN
3318   -- Update the calling sequence
3319   --
3320   current_calling_sequence :=
3321     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_awt_group<-'
3322     ||P_calling_sequence;
3323 
3324   IF p_invoice_rec.awt_group_id is not null THEN
3325 
3326     --validate awt_group_id
3327     SELECT group_id, inactive_date
3328       INTO l_awt_group_id, l_inactive_date
3329       FROM ap_awt_groups
3330      WHERE group_id = p_invoice_rec.awt_group_id;
3331 
3332   END IF;
3333 
3334   IF (p_invoice_rec.awt_group_name is NOT NULL) THEN
3335     --validate awt group name and retrieve awt group id
3336     SELECT group_id, inactive_date
3337       INTO l_awt_group_id_per_name, l_inactive_date_per_name
3338       FROM ap_awt_groups
3339      WHERE name = p_invoice_rec.awt_group_name;
3340   END IF;
3341 
3342   IF (l_awt_group_id is NOT NULL) AND
3343      (l_awt_group_id_per_name is NOT NULL) AND
3344      (l_awt_group_id <> l_awt_group_id_per_name) THEN
3345 
3346     -------------------------------------------------------------------------
3347     -- Step 1
3348     -- Check for AWT Group Id and Group Name Inconsistency.
3349     -------------------------------------------------------------------------
3350     debug_info := '(Check AWT Group 1) Check for AWT Group Id and Group Name'
3351                   ||' Inconsistency.';
3352     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3353       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3354                                     debug_info);
3355     END IF;
3356 
3357     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3358           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3359             p_invoice_rec.invoice_id,
3360             'INCONSISTENT AWT GROUP',
3361             p_default_last_updated_by,
3362             p_default_last_update_login,
3363             current_calling_sequence) <> TRUE) THEN
3364       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3365         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3366         'insert_rejections<-'||current_calling_sequence);
3367       END IF;
3368       RAISE awt_group_check_failure;
3369     END IF;
3370     l_current_invoice_status := 'N';
3371 
3372   ELSE
3373 
3374     ------------------------------------------------------------------------
3375     -- Step 2
3376     -- Check for Inactive AWT Group
3377     ------------------------------------------------------------------------
3378     debug_info := '(Check AWT Group 2) Check for Inactive AWT Group';
3379     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3380       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3381                                     debug_info);
3382     END IF;
3383 
3384     IF ((l_awt_group_id is NULL) and
3385         (l_awt_group_id_per_name is NOT NULL)) THEN
3386 
3387       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3388          nvl(l_inactive_date_per_name,
3389              AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3390         --------------------------------------------------------------
3391         -- inactive AWT group (per name)
3392         --
3393         ---------------------------------------------------------------
3394         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3395                              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3396                             p_invoice_rec.invoice_id,
3397             'INACTIVE AWT GROUP',
3398             p_default_last_updated_by,
3399             p_default_last_update_login,
3400             current_calling_sequence) <> TRUE) THEN
3401           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3402             AP_IMPORT_UTILITIES_PKG.Print(
3403             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3404             'insert_rejections<-'||current_calling_sequence);
3405           END IF;
3406           RAISE awt_group_check_failure;
3407         END IF;
3408 
3409         l_current_invoice_status := 'N';
3410 
3411       END IF; -- Inactive AWT Group per name
3412 
3413     ELSIF (((l_awt_group_id is NOT NULL) and
3414             (l_awt_group_id_per_name is NULL)) OR
3415            ((l_awt_group_id is NOT NULL) and
3416             (l_awt_group_id_per_name is NOT NULL) and
3417             (l_awt_group_id = l_awt_group_id_per_name))) THEN
3418 
3419       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3420          nvl(l_inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3421 
3422         --------------------------------------------------------------
3423         -- inactive AWT group (as per id)
3424         --
3425         --------------------------------------------------------------
3426         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3427           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3428             p_invoice_rec.invoice_id,
3429             'INACTIVE AWT GROUP',
3430             p_default_last_updated_by,
3431             p_default_last_update_login,
3432             current_calling_sequence) <> TRUE) THEN
3433           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3434             AP_IMPORT_UTILITIES_PKG.Print(
3435             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3436             'insert_rejections<-'||current_calling_sequence);
3437           END IF;
3438           RAISE awt_group_check_failure;
3439         END IF;
3440 
3441         l_current_invoice_status := 'N';
3442 
3443       END IF; -- Inactive AWT Group per id
3444 
3445     END IF; -- awt group id is null and awt group id per name is not null
3446 
3447   END IF; -- awt group id is not null, awt group id per name is not null
3448           -- but they differ
3449 
3450   IF (l_awt_group_id is not null) then
3451     p_awt_group_id := l_awt_group_id;
3452   ELSIF (l_awt_group_id_per_name IS NOT NULL) THEN
3453     p_awt_group_id := l_awt_group_id_per_name;
3454   ELSE
3455     IF ((l_current_invoice_status <> 'N') AND
3456            (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')) THEN
3457        -- Get awt group id from supplier site
3458       BEGIN
3459         SELECT awt_group_id
3460           INTO p_awt_group_id
3461       FROM po_vendor_sites
3462          WHERE vendor_id = p_invoice_rec.vendor_id
3463          AND vendor_site_id = p_invoice_rec.vendor_site_id;
3464       EXCEPTION
3465     WHEN no_data_found THEN
3466       RAISE awt_group_check_failure;
3467     WHEN OTHERS THEN
3468       RAISE awt_group_check_failure;
3469       END;
3470     END IF;
3471   END IF;
3472 
3473 
3474   p_current_invoice_status := l_current_invoice_status;
3475 
3476   RETURN (TRUE);
3477 
3478 EXCEPTION
3479   WHEN no_data_found THEN
3480     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3481        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3482          p_invoice_rec.invoice_id,
3483          'INVALID AWT GROUP',
3484          p_default_last_updated_by,
3485          p_default_last_update_login,
3486          current_calling_sequence) <> TRUE) THEN
3487       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3488         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3489         'insert_rejections<-'||current_calling_sequence);
3490       END IF;
3491       RAISE awt_group_check_failure;
3492     END IF;
3493 
3494     l_current_invoice_status := 'N';
3495     p_current_invoice_status := l_current_invoice_status;
3496     RETURN (TRUE);
3497 
3498   WHEN OTHERS THEN
3499     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3500       AP_IMPORT_UTILITIES_PKG.Print(
3501       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3502     END IF;
3503 
3504     IF (SQLCODE < 0) then
3505       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3506     AP_IMPORT_UTILITIES_PKG.Print(
3507          AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
3508       END IF;
3509     END IF;
3510     RETURN(FALSE);
3511 
3512 END v_check_invalid_awt_group;
3513 
3514 --bug6639866
3515 ----------------------------------------------------------------------------
3516 -- This function is used to validate that the pay awt information
3517 -- is valid and consistent.
3518 --
3519 ----------------------------------------------------------------------------
3520 FUNCTION v_check_invalid_pay_awt_group (
3521     p_invoice_rec        IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3522     p_pay_awt_group_id                  OUT NOCOPY NUMBER,
3523     p_default_last_updated_by    IN            NUMBER,
3524     p_default_last_update_login  IN            NUMBER,
3525     p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
3526     p_calling_sequence           IN            VARCHAR2) RETURN BOOLEAN
3527 IS
3528 
3529 pay_awt_group_check_failure     EXCEPTION;
3530 l_current_invoice_status    VARCHAR2(1) := 'Y';
3531 l_pay_awt_group_id              AP_INVOICES.pay_AWT_GROUP_ID%TYPE;
3532 l_pay_awt_group_id_per_name     AP_INVOICES.pay_AWT_GROUP_ID%TYPE;
3533 l_inactive_date             DATE;
3534 l_inactive_date_per_name    DATE;
3535 current_calling_sequence    VARCHAR2(2000);
3536 debug_info                  VARCHAR2(500);
3537 
3538 BEGIN
3539   -- Update the calling sequence
3540   --
3541   current_calling_sequence :=
3542     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_awt_group<-'
3543     ||P_calling_sequence;
3544 
3545   IF p_invoice_rec.pay_awt_group_id is not null THEN
3546 
3547     --validate pay_awt_group_id
3548     SELECT group_id, inactive_date
3549     INTO l_pay_awt_group_id, l_inactive_date
3550       FROM ap_awt_groups
3551      WHERE group_id = p_invoice_rec.pay_awt_group_id;
3552 
3553   END IF;
3554 
3555   IF (p_invoice_rec.pay_awt_group_name is NOT NULL) THEN
3556     --validate pay awt group name and retrieve pay awt group id
3557     SELECT group_id, inactive_date
3558       INTO l_pay_awt_group_id_per_name, l_inactive_date_per_name
3559       FROM ap_awt_groups
3560      WHERE name = p_invoice_rec.pay_awt_group_name;
3561   END IF;
3562 
3563   IF (l_pay_awt_group_id is NOT NULL) AND
3564      (l_pay_awt_group_id_per_name is NOT NULL) AND
3565      (l_pay_awt_group_id <> l_pay_awt_group_id_per_name) THEN
3566 
3567     -------------------------------------------------------------------------
3568     -- Step 1
3569     -- Check for pay AWT Group Id and Group Name Inconsistency.
3570     -------------------------------------------------------------------------
3571     debug_info := '(Check AWT Group 1) Check for pay AWT Group Id and pay Group Name'
3572                   ||' Inconsistency.';
3573     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3574       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3575                                     debug_info);
3576     END IF;
3577 
3578     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3579           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3580             p_invoice_rec.invoice_id,
3581             'INCONSISTENT PAY AWT GROUP',
3582             p_default_last_updated_by,
3583             p_default_last_update_login,
3584 current_calling_sequence) <> TRUE) THEN
3585       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3586         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3587         'insert_rejections<-'||current_calling_sequence);
3588       END IF;
3589       RAISE pay_awt_group_check_failure;
3590     END IF;
3591     l_current_invoice_status := 'N';
3592 
3593   ELSE
3594 
3595     ------------------------------------------------------------------------
3596     -- Step 2
3597     -- Check for Inactive pay AWT Group
3598     ------------------------------------------------------------------------
3599     debug_info := '(Check AWT Group 2) Check for Inactive pay AWT Group';
3600     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3601       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3602                                     debug_info);
3603     END IF;
3604 
3605     IF ((l_pay_awt_group_id is NULL) and
3606         (l_pay_awt_group_id_per_name is NOT NULL)) THEN
3607 
3608       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3609          nvl(l_inactive_date_per_name,
3610              AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3611         --------------------------------------------------------------
3612         -- inactive pay AWT group (per name)
3613         --
3614         ---------------------------------------------------------------
3615         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3616            (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3617             p_invoice_rec.invoice_id,
3618             'INACTIVE PAY AWT GROUP',
3619             p_default_last_updated_by,
3620             p_default_last_update_login,
3621             current_calling_sequence) <> TRUE) THEN
3622           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3623             AP_IMPORT_UTILITIES_PKG.Print(
3624             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3625             'insert_rejections<-'||current_calling_sequence);
3626           END IF;
3627           RAISE pay_awt_group_check_failure;
3628         END IF;
3629 
3630         l_current_invoice_status := 'N';
3631 
3632       END IF; -- Inactive pay AWT Group per name
3633 
3634     ELSIF (((l_pay_awt_group_id is NOT NULL) and
3635             (l_pay_awt_group_id_per_name is NULL)) OR
3636            ((l_pay_awt_group_id is NOT NULL) and
3637             (l_pay_awt_group_id_per_name is NOT NULL) and
3638             (l_pay_awt_group_id = l_pay_awt_group_id_per_name))) THEN
3639 
3640       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
3641          nvl(l_inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
3642 
3643         --------------------------------------------------------------
3644         -- inactive pay AWT group (as per id)
3645         --
3646         --------------------------------------------------------------
3647         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3648           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3649             p_invoice_rec.invoice_id,
3650             'INACTIVE PAY AWT GROUP',
3651             p_default_last_updated_by,
3652             p_default_last_update_login,
3653             current_calling_sequence) <> TRUE) THEN
3654  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3655             AP_IMPORT_UTILITIES_PKG.Print(
3656             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3657             'insert_rejections<-'||current_calling_sequence);
3658           END IF;
3659           RAISE pay_awt_group_check_failure;
3660         END IF;
3661 
3662         l_current_invoice_status := 'N';
3663 
3664       END IF; -- Inactive pay AWT Group per id
3665 
3666     END IF; -- pay awt group id is null and pay awt group id per name is not null
3667 
3668   END IF; -- pay awt group id is not null, pay awt group id per name is not null
3669           -- but they differ
3670 
3671   IF (l_pay_awt_group_id is not null) then
3672     p_pay_awt_group_id := l_pay_awt_group_id;
3673   ELSIF (l_pay_awt_group_id_per_name IS NOT NULL) THEN
3674     p_pay_awt_group_id := l_pay_awt_group_id_per_name;
3675   ELSE
3676     IF ((l_current_invoice_status <> 'N') AND
3677            (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST')) THEN
3678        -- Get pay awt group id from supplier site
3679       BEGIN
3680         SELECT pay_awt_group_id
3681           INTO p_pay_awt_group_id
3682       FROM po_vendor_sites
3683          WHERE vendor_id = p_invoice_rec.vendor_id
3684          AND vendor_site_id = p_invoice_rec.vendor_site_id;
3685       EXCEPTION
3686     WHEN no_data_found THEN
3687       RAISE pay_awt_group_check_failure;
3688     WHEN OTHERS THEN
3689       RAISE pay_awt_group_check_failure;
3690       END;
3691      END IF;
3692     END IF;
3693 
3694 
3695   p_current_invoice_status := l_current_invoice_status;
3696 
3697   RETURN (TRUE);
3698 
3699 EXCEPTION
3700   WHEN no_data_found THEN
3701     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3702        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3703          p_invoice_rec.invoice_id,
3704          'INVALID PAY AWT GROUP',
3705          p_default_last_updated_by,
3706          p_default_last_update_login,
3707          current_calling_sequence) <> TRUE) THEN
3708       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3709         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3710         'insert_rejections<-'||current_calling_sequence);
3711       END IF;
3712       RAISE pay_awt_group_check_failure;
3713     END IF;
3714 
3715     l_current_invoice_status := 'N';
3716     p_current_invoice_status := l_current_invoice_status;
3717     RETURN (TRUE);
3718 
3719   WHEN OTHERS THEN
3720     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3721       AP_IMPORT_UTILITIES_PKG.Print(
3722       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3723     END IF;
3724  IF (SQLCODE < 0) then
3725       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3726     AP_IMPORT_UTILITIES_PKG.Print(
3727          AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
3728       END IF;
3729     END IF;
3730     RETURN(FALSE);
3731 
3732 END v_check_invalid_pay_awt_group;
3733 
3734 ----------------------------------------------------------------------------
3735 -- This function is used to validate exchange rate information
3736 -- for the invoice.
3737 ----------------------------------------------------------------------------
3738 FUNCTION v_check_exchange_rate_type (
3739     p_invoice_rec     IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
3740     p_exchange_rate                 OUT NOCOPY  NUMBER,
3741     p_exchange_date                 OUT NOCOPY  DATE,
3742     p_base_currency_code         IN             VARCHAR2,
3743     p_multi_currency_flag        IN             VARCHAR2,
3744     p_set_of_books_id            IN             NUMBER,
3745     p_default_exchange_rate_type IN             VARCHAR2,
3746     p_make_rate_mandatory_flag   IN             VARCHAR2,
3747     p_default_last_updated_by    IN             NUMBER,
3748     p_default_last_update_login  IN             NUMBER,
3749     p_current_invoice_status     IN OUT NOCOPY  VARCHAR2,
3750     p_calling_sequence           IN             VARCHAR2) RETURN BOOLEAN
3751 IS
3752 
3753 exchange_rate_type_failure    EXCEPTION;
3754 l_conversion_type             VARCHAR2(30) := p_invoice_rec.exchange_rate_type;
3755 l_exchange_date               DATE := p_invoice_rec.exchange_date;
3756 l_exchange_rate               NUMBER := p_invoice_rec.exchange_rate;
3757 l_current_invoice_status      VARCHAR2(1) := 'Y';
3758 l_valid_conversion_type       VARCHAR2(30);
3759 current_calling_sequence      VARCHAR2(2000);
3760 debug_info                    VARCHAR2(500);
3761 
3762 BEGIN
3763   -- Update the calling sequence
3764   --
3765   current_calling_sequence :=
3766     'AP_IMPORT_VALIDATION_PKG.v_check_invalid_inv_curr_code<-'
3767     ||P_calling_sequence;
3768 
3769   IF (NVL(p_multi_currency_flag,'N') = 'Y') AND
3770      (p_base_currency_code <> p_invoice_rec.invoice_currency_code) Then
3771 
3772     -------------------------------------------------------------------------
3773     -- Step 1
3774     -- Check for invalid exchange rate type
3775     -------------------------------------------------------------------------
3776     debug_info := '(Check Exchange Rate Type 1) Check for invalid Exchange '
3777                   ||'Rate Type';
3778     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3779       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3780                                     debug_info);
3781     END IF;
3782 
3783     IF (l_conversion_type is NULL) Then
3784       debug_info := '(Check Exchange Rate Type 1a) Get Default Exchange '
3785                     ||'Rate Type';
3786       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3787         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3788                                       debug_info);
3789       END IF;
3790       l_conversion_type := p_default_exchange_rate_type;
3791     END IF;
3792 
3793     IF (l_conversion_type is NOT NULL) Then
3794       debug_info :=
3795            '(Check Exchange Rate Type 1b) Check if Rate Type is valid';
3796       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3797         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3798                                       debug_info);
3799       END IF;
3800 
3801       BEGIN
3802         SELECT 'X'
3803           INTO l_valid_conversion_type
3804           FROM gl_daily_conversion_types
3805           WHERE conversion_type = l_conversion_type;
3806 
3807       EXCEPTION
3808         WHEN no_data_found THEN
3809           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3810                    (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3811                     p_invoice_rec.invoice_id,
3812                     'INVALID EXCH RATE TYPE',
3813                     p_default_last_updated_by,
3814                     p_default_last_update_login,
3815                     current_calling_sequence) <> TRUE) THEN
3816             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3817               AP_IMPORT_UTILITIES_PKG.Print(
3818               AP_IMPORT_INVOICES_PKG.g_debug_switch,
3819               'insert_rejections<-'||current_calling_sequence);
3820             END IF;
3821             RAISE exchange_rate_type_failure;
3822           END IF;
3823           l_current_invoice_status := 'N';
3824 
3825       END;
3826 
3827     END IF; -- conversion type not null
3828 
3829     -------------------------------------------------------------------------
3830     -- Step 2
3831     -- Get exchange date
3832     -------------------------------------------------------------------------
3833     IF (p_invoice_rec.exchange_date IS NULL) THEN
3834       debug_info :=
3835           '(Check Exchange Rate Type 2) Get Sysdate as Exchange Date';
3836       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3837         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3838                                       debug_info);
3839       END IF;
3840 
3841       -- Invoice date was initialized to sysdate if null at the beginning
3842       -- of the invoice validation process.
3843       l_exchange_date := nvl(p_invoice_rec.gl_date,
3844                  p_invoice_rec.invoice_date);
3845     END IF;
3846 
3847 
3848     IF (l_valid_conversion_type ='X') Then
3849       ----------------------------------------------------------------------
3850       -- Step 3
3851       -- Check for Inconsistent exchange rate
3852       ----------------------------------------------------------------------
3853       debug_info := '(Check Exchange Rate Type 3a) Check for inconsistent '
3854                     ||'Exchange Rate, if type valid';
3855       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3856         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3857                                       debug_info);
3858       END IF;
3859       debug_info := 'l_coversion_type: '||l_conversion_type ||'  '||
3860                      'p_invoice_rec.exchange_rate: '||p_invoice_rec.exchange_rate;
3861 
3862       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3863         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3864                                       debug_info);
3865       END IF;
3866 
3867       IF ((l_conversion_type <> 'User') AND
3868           (p_invoice_rec.exchange_rate is NOT NULL)) AND   -- Bug 5003374
3869            nvl(ap_utilities_pkg.get_exchange_rate(       -- Added this Condition.
3870                                 p_invoice_rec.invoice_currency_code,
3871                                 p_base_currency_code,
3872                                 l_conversion_type,
3873                                 l_exchange_date,
3874                                 current_calling_sequence),-999) <> p_exchange_rate THEN
3875         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3876             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3877               p_invoice_rec.invoice_id,
3878              'INCONSISTENT RATE',
3879               p_default_last_updated_by,
3880               p_default_last_update_login,
3881               current_calling_sequence) <> TRUE) THEN
3882           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3883             AP_IMPORT_UTILITIES_PKG.Print(
3884             AP_IMPORT_INVOICES_PKG.g_debug_switch,
3885             'insert_rejections<-'||current_calling_sequence);
3886           END IF;
3887           RAISE exchange_rate_type_failure;
3888         END IF;
3889 
3890         l_current_invoice_status := 'N';
3891 
3892       ELSIF ((l_conversion_type = 'User') AND
3893               (p_invoice_rec.exchange_rate is NULL))  AND
3894              (AP_UTILITIES_PKG.calculate_user_xrate (
3895                   p_invoice_rec.invoice_currency_code,
3896                   p_base_currency_code,
3897                   l_exchange_date,
3898                   l_conversion_type) <> 'Y') THEN
3899         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3900                                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3901                                       p_invoice_rec.invoice_id,
3902                                      'NO EXCHANGE RATE',
3903                                       p_default_last_updated_by,
3904                                       p_default_last_update_login,
3905                                       current_calling_sequence) <> TRUE) THEN
3906           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
3907             AP_IMPORT_UTILITIES_PKG.Print(
3908               AP_IMPORT_INVOICES_PKG.g_debug_switch,
3909               'insert_rejections<-'||current_calling_sequence);
3910           END IF;
3911           RAISE exchange_rate_type_failure;
3912         END IF;
3913 
3914         l_current_invoice_status := 'N';
3915 
3916       ELSIF ((l_conversion_type <> 'User') AND
3917        (p_invoice_rec.exchange_rate is NULL))   Then
3918         null;
3919 
3920         debug_info := '(Check Exchange Rate Type 3b) Get Exchange Rate for'
3921                       ||' type other than User';
3922         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3923           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3924                                         debug_info);
3925         END IF;
3926 
3927         l_exchange_rate := ap_utilities_pkg.get_exchange_rate(
3928                 p_invoice_rec.invoice_currency_code,
3929                 p_base_currency_code,
3930                 l_conversion_type,
3931                 l_exchange_date,
3932                 current_calling_sequence);
3933         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3934           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
3935           '----------------> exchange_rate = '|| to_char(l_exchange_rate)
3936           ||'set_of_books_id = '||to_char(p_set_of_books_id)
3937           ||'invoice_currency_code = '||p_invoice_rec.invoice_currency_code
3938           ||'exchange_date= '||to_char(l_exchange_date)
3939           ||'conversion_type = '||l_conversion_type);
3940         END IF;
3941 
3942         IF (l_exchange_rate IS NULL) THEN
3943 
3944           IF (NVL(p_make_rate_mandatory_flag,'N') = 'Y') then
3945             debug_info :=
3946               '(Check Exchange Rate Type 3c) Reject:No Exchange Rate ';
3947             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3948               AP_IMPORT_UTILITIES_PKG.Print(
3949                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3950             END IF;
3951 
3952             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3953                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3954                      p_invoice_rec.invoice_id,
3955                      'NO EXCHANGE RATE',
3956                      p_default_last_updated_by,
3957                      p_default_last_update_login,
3958                      current_calling_sequence) <> TRUE) THEN
3959               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3960                 AP_IMPORT_UTILITIES_PKG.Print(
3961                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
3962                   'insert_rejections<-'||current_calling_sequence);
3963               END IF;
3964               RAISE exchange_rate_type_failure;
3965             END IF;
3966 
3967             l_current_invoice_status := 'N';
3968 
3969           ELSE
3970             debug_info := '(Check Exchange Rate Type 3d) No Exchange'
3971                           ||' Rate:Rate Not Reqd ';
3972             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3973               AP_IMPORT_UTILITIES_PKG.Print(
3974                      AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
3975             END IF;
3976 
3977           END IF; -- make_rate_mandatory
3978 
3979         END IF;  -- exchange_rate is null
3980             --4091870
3981        ELSIF ((l_conversion_type = 'User') AND
3982                     (p_exchange_rate <= 0))  then
3983 
3984                 IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
3985                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
3986                      p_invoice_rec.invoice_id,
3987                      'INVALID EXCH RATE',
3988                      p_default_last_updated_by,
3989                      p_default_last_update_login,
3990                      current_calling_sequence) <> TRUE) THEN
3991               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
3992                 AP_IMPORT_UTILITIES_PKG.Print(
3993                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
3994                   'insert_rejections<-'||current_calling_sequence);
3995               END IF;
3996               RAISE exchange_rate_type_failure;
3997             END IF;
3998 
3999                 l_current_invoice_status := 'N';
4000               --4091870 end
4001       END IF; -- l_conversion_type <>User
4002 
4003 
4004       IF ((l_conversion_type <> 'User') AND
4005           (p_invoice_rec.exchange_rate is NOT NULL) AND
4006           (p_invoice_rec.exchange_rate <> l_exchange_rate)) Then
4007 
4008         debug_info := '(Check Exchange Rate Type 3e) Exchange rate in '
4009                       ||'interface differs rate defined';
4010         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4011           AP_IMPORT_UTILITIES_PKG.Print(
4012                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4013         END IF;
4014 
4015         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4016              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4017               p_invoice_rec.invoice_id,
4018               'INCONSISTENT RATE',
4019               p_default_last_updated_by,
4020                p_default_last_update_login,
4021                current_calling_sequence) <> TRUE) THEN
4022           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4023             AP_IMPORT_UTILITIES_PKG.Print(
4024               AP_IMPORT_INVOICES_PKG.g_debug_switch,
4025               'insert_rejections<-'||current_calling_sequence);
4026           END IF;
4027           RAISE exchange_rate_type_failure;
4028         END IF;
4029         l_current_invoice_status := 'N';
4030 
4031       END IF; -- exchange rate in interface other than defined in system
4032 
4033     END IF; -- l_valid_conversion_type = 'X'
4034 
4035   ELSIF ((nvl(p_multi_currency_flag,'N') = 'N') AND
4036          (p_base_currency_code <> p_invoice_rec.invoice_currency_code)) THEN
4037 
4038     -------------------------------------------------------------------------
4039     -- Step 4
4040     -- Check for Inconsistent Information Entered
4041     -------------------------------------------------------------------------
4042     debug_info := '(Check Exchange Rate Type 9) Check for inconsistent '
4043                   ||'Information Entered';
4044     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4045       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4046                                     debug_info);
4047     END IF;
4048 
4049     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4050         (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4051           p_invoice_rec.invoice_id,
4052          'INCONSISTENT INFO ENTERED',
4053           p_default_last_updated_by,
4054           p_default_last_update_login,
4055           current_calling_sequence) <> TRUE) THEN
4056       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4057         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4058            'insert_rejections<-'||current_calling_sequence);
4059       END IF;
4060       RAISE exchange_rate_type_failure;
4061     END IF;
4062 
4063     l_current_invoice_status := 'N';
4064 
4065   END IF; -- multi currency flag and foreign currency invoice
4066 
4067   p_exchange_rate := l_exchange_rate;
4068   p_exchange_date := l_exchange_date;
4069   p_current_invoice_status := l_current_invoice_status;
4070   RETURN (TRUE);
4071 
4072 EXCEPTION
4073   WHEN OTHERS THEN
4074     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4075       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4076     END IF;
4077 
4078   IF (SQLCODE < 0) then
4079     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4080       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
4081     END IF;
4082   END IF;
4083 
4084   RETURN(FALSE);
4085 
4086 END v_check_exchange_rate_type;
4087 
4088 ------------------------------------------------------------------
4089 -- This function is used to validate payment terms information.
4090 --
4091 ------------------------------------------------------------------
4092 FUNCTION v_check_invalid_terms (
4093     p_invoice_rec  IN      AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
4094     p_terms_id                      OUT NOCOPY NUMBER,
4095     p_terms_date                    OUT NOCOPY DATE,
4096     p_terms_date_basis           IN            VARCHAR2,
4097     p_default_last_updated_by    IN            NUMBER,
4098     p_default_last_update_login  IN            NUMBER,
4099     p_current_invoice_status     IN OUT NOCOPY VARCHAR2,
4100     p_calling_sequence           IN            VARCHAR2) RETURN BOOLEAN
4101 IS
4102 
4103 terms_check_failure           EXCEPTION;
4104 l_current_invoice_status      VARCHAR2(1) := 'Y';
4105 l_term_id                     NUMBER := Null;
4106 l_term_id_per_name            NUMBER := Null;
4107 l_start_date_active           DATE;
4108 l_end_date_active             DATE;
4109 l_start_date_active_per_name  DATE;
4110 l_end_date_active_per_name    DATE;
4111 current_calling_sequence      VARCHAR2(2000);
4112 debug_info                    VARCHAR2(500);
4113 
4114 l_term_name                     VARCHAR2(50);--Bug 4115712
4115 l_no_calendar_exists            VARCHAR2(1); --Bug 4115712
4116 
4117 BEGIN
4118   -- Update the calling sequence
4119   --
4120   current_calling_sequence :=
4121      'AP_IMPORT_VALIDATION_PKG.v_check_invalid_terms<-'
4122      ||P_calling_sequence;
4123   --------------------------------------------------------------------------
4124   -- Fidelity needs to ignore terms info if you have PO as well.
4125   -- In this case we should not check/reject for inconsistency
4126   -- instead take the terms from PO / Supplier.
4127   -- terms defaulting: If terms provided in the interface (default
4128   -- from supplier using IG) use them unconditionally. If terms not provided
4129   -- and PO exists, use PO terms else default terms from Supplier Site.
4130   --------------------------------------------------------------------------
4131   BEGIN
4132 
4133     IF (p_invoice_rec.terms_id is not null) THEN
4134      --validate term_id
4135      SELECT term_id, start_date_active, end_date_active
4136        INTO l_term_id, l_start_date_active, l_end_date_active
4137        FROM ap_terms
4138       WHERE term_id = p_invoice_rec.terms_id;
4139     END IF;
4140 
4141     IF (p_invoice_rec.terms_name is not null) THEN
4142      --validate terms name and retrieve term id
4143      SELECT term_id, start_date_active, end_date_active
4144        INTO l_term_id_per_name, l_start_date_active_per_name,
4145             l_end_date_active_per_name
4146        FROM ap_terms
4147       WHERE name = p_invoice_rec.terms_name;
4148     END IF;
4149 
4150   EXCEPTION
4151 
4152     WHEN no_data_found THEN
4153       ----------------------------------------------------------------------
4154       -- Step 1
4155       -- Check invalid terms.
4156       ----------------------------------------------------------------------
4157      debug_info := '(Check Invalid Terms 1) Check for invalid Terms.';
4158      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4159        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4160                                      debug_info);
4161      END IF;
4162 
4163      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4164           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4165             p_invoice_rec.invoice_id,
4166             'INVALID TERMS',
4167             p_default_last_updated_by,
4168             p_default_last_update_login,
4169             current_calling_sequence) <> TRUE) THEN
4170        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4171          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4172          'insert_rejections<- '||current_calling_sequence);
4173        END IF;
4174        RAISE terms_check_failure;
4175     END IF;
4176 
4177     l_current_invoice_status := 'N';
4178     p_current_invoice_status := l_current_invoice_status;
4179 
4180   END;
4181 
4182   --------------------------------------------------------------
4183   -- Step 2
4184   -- If no payment term, get from PO or Supplier Site.
4185   -- Retropricing: For PPA's p_invoice_rec.terms_id is NOT NULL
4186   --------------------------------------------------------------
4187   IF ((p_invoice_rec.terms_id is NULL) AND
4188       (p_invoice_rec.terms_name is NULL)) THEN
4189 
4190     IF (p_invoice_rec.po_number is NOT NULL) Then
4191       debug_info :=
4192           '(Check Invalid Terms 2.1) Get term_id from header po_number';
4193       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4194         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4195                                       debug_info);
4196       END IF;
4197 
4198       SELECT terms_id
4199         INTO l_term_id
4200         FROM po_headers
4201        WHERE segment1 = p_invoice_rec.po_number
4202          AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
4203     END IF;
4204 
4205     -- no term from header level po_number, try lines level po_number
4206     IF (l_term_id is null ) THEN
4207       debug_info :=
4208          '(Check Invalid Terms 2.2) Get term_id from lines po_numbers';
4209       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4210         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4211                                       debug_info);
4212       END IF;
4213       BEGIN
4214         SELECT p.terms_id
4215           INTO l_term_id
4216           FROM po_headers p, ap_invoice_lines_interface l
4217          WHERE p.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
4218            AND ((l.po_header_id = p.po_header_id) OR
4219                 (l.po_number    = p.segment1))
4220            AND l.invoice_id = p_invoice_rec.invoice_id
4221            AND p.terms_id IS NOT NULL
4222          GROUP BY p.terms_id;
4223       EXCEPTION
4224         WHEN NO_DATA_FOUND THEN
4225           NULL;
4226         WHEN TOO_MANY_ROWS THEN
4227           l_term_id        := null;
4228           l_current_invoice_status := 'N';
4229           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4230                                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4231                                  p_invoice_rec.invoice_id,
4232                                  'INCONSISTENT TERMS INFO',
4233                                  p_default_last_updated_by,
4234                                  p_default_last_update_login,
4235                                  current_calling_sequence) <> TRUE) THEN
4236             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4237               AP_IMPORT_UTILITIES_PKG.Print(
4238               AP_IMPORT_INVOICES_PKG.g_debug_switch,
4239               'insert_rejections<- '||current_calling_sequence);
4240             END IF;
4241             RAISE terms_check_failure;
4242           END IF;
4243       END;
4244 
4245       -- no term from line level PO, try line level receipt
4246       IF (l_term_id is null) THEN
4247         debug_info := '(Check Invalid Terms 2.3) Get term_id from lines'
4248                       ||' receipt';
4249         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4250           AP_IMPORT_UTILITIES_PKG.Print(
4251              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
4252         END IF;
4253         BEGIN
4254           SELECT p.terms_id
4255             INTO l_term_id
4256             FROM rcv_transactions r,
4257                  po_headers p,
4258                  ap_invoice_lines_interface l
4259            WHERE p.po_header_id = r.po_header_id
4260              AND r.transaction_id = l.rcv_transaction_id
4261              AND l.invoice_id = p_invoice_rec.invoice_id
4262              AND p.terms_id IS NOT NULL
4263            GROUP BY p.terms_id;
4264         EXCEPTION
4265           WHEN NO_DATA_FOUND THEN
4266             NULL;
4267           WHEN TOO_MANY_ROWS THEN
4268             debug_info := 'too many rows';
4269             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4270               AP_IMPORT_UTILITIES_PKG.Print(
4271                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
4272             END IF;
4273             l_term_id        := null;
4274             l_current_invoice_status := 'N';
4275             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4276                                   (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4277                                    p_invoice_rec.invoice_id,
4278                                    'INCONSISTENT TERMS INFO',
4279                                    p_default_last_updated_by,
4280                                    p_default_last_update_login,
4281                                    current_calling_sequence) <> TRUE) THEN
4282               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4283                 AP_IMPORT_UTILITIES_PKG.Print(
4284                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
4285                 'insert_rejections<- '||current_calling_sequence);
4286               END IF;
4287               RAISE terms_check_failure;
4288             END IF;
4289         END;
4290 
4291       END IF; -- end get term from line level receipt
4292 
4293     END IF; -- end get term from line level
4294 
4295     -- no term from header or line level
4296     IF ( (nvl(l_current_invoice_status,'Y') = 'Y') AND -- not rejected already
4297          (l_term_id is null) AND
4298          (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST') ) Then
4299 
4300       debug_info := '(Check Invalid Terms 2.4) Get term_id from supplier site';
4301       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4302         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4303                                       debug_info);
4304       END IF;
4305 
4306       SELECT terms_id
4307       INTO   l_term_id
4308       FROM   po_vendor_sites
4309       WHERE  vendor_id      = p_invoice_rec.vendor_id
4310       AND    vendor_site_id = p_invoice_rec.vendor_site_id;
4311 
4312     ELSIF ( (nvl(l_current_invoice_status,'Y') = 'Y') AND -- not rejected already
4313          (l_term_id is null) AND
4314          (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') ) Then
4315 
4316       debug_info := '(Check Invalid Terms 2.4) Get term_id from financials options';
4317       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4318         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4319                                       debug_info);
4320       END IF;
4321 
4322       SELECT terms_id
4323       INTO   l_term_id
4324       FROM   ap_product_setup;
4325       -- Bug 5519299. Terms_Id for Payment request based on ap_product_setup
4326       -- FROM   financials_system_parameters
4327       -- WHERE  org_id = p_invoice_rec.org_id;
4328 
4329     END IF;
4330 
4331     IF ( nvl(l_current_invoice_status,'Y') = 'Y' ) THEN
4332       IF ( l_term_id is null ) THEN
4333         debug_info := '(Check Invalid Terms 2.5) no term_id found, '
4334                       ||'invoice rejected';
4335         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4336           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4337                                         debug_info);
4338         END IF;
4339 
4340         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4341                              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4342                               p_invoice_rec.invoice_id,
4343                               'NO TERMS INFO',
4344                               p_default_last_updated_by,
4345                               p_default_last_update_login,
4346                               current_calling_sequence) <> TRUE) THEN
4347           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4348             AP_IMPORT_UTILITIES_PKG.Print(
4349             AP_IMPORT_INVOICES_PKG.g_debug_switch,
4350             'insert_rejections<- '||current_calling_sequence);
4351           END IF;
4352           RAISE terms_check_failure;
4353         END IF;
4354 
4355         l_current_invoice_status := 'N';
4356 
4357       ELSE
4358         debug_info := '(Check Invalid Terms 2.6) getting term active date';
4359         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4360           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4361                                         debug_info);
4362         END IF;
4363 
4364         SELECT start_date_active, end_date_active
4365           INTO l_start_date_active, l_end_date_active
4366           FROM ap_terms
4367          WHERE term_id = l_term_id;
4368 
4369       END IF; -- l_terms_id is null
4370     END IF; -- nvl(l_current_invoice_status,'Y') = 'Y'
4371 
4372   END IF; -- interface invoice terms_id and terms_name are null
4373 
4374   --------------------------------------------------------------------------
4375   -- Step 3
4376   -- Check Inconsistent and Inactive terms info.
4377   ---------------------------------------------------------------------------
4378   IF ((l_term_id is not null) AND
4379       (l_term_id_per_name is not null) AND
4380       (l_term_id <> l_term_id_per_name)) THEN
4381 
4382     debug_info := '(Check Invalid Terms 3) Check for inconsistent Terms id '
4383                    ||'and Name.';
4384     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4385       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4386                                     debug_info);
4387     END IF;
4388 
4389     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4390           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4391             p_invoice_rec.invoice_id,
4392             'INCONSISTENT TERMS INFO',
4393             p_default_last_updated_by,
4394             p_default_last_update_login,
4395             current_calling_sequence) <> TRUE) THEN
4396       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4397         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4398         'insert_rejections<- '||current_calling_sequence);
4399       END IF;
4400       RAISE terms_check_failure;
4401     END IF;
4402 
4403     l_current_invoice_status := 'N';
4404 
4405   ELSIF ((l_term_id is null) and
4406          (l_term_id_per_name is NOT NULL)) THEN
4407 
4408     IF (not((AP_IMPORT_INVOICES_PKG.g_inv_sysdate >
4409              nvl(l_start_date_active_per_name,
4410                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate - 1))
4411         AND (AP_IMPORT_INVOICES_PKG.g_inv_sysdate <
4412              nvl(l_end_date_active_per_name,
4413                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate + 1)))) THEN
4414 
4415       -----------------------------------------------------------------------
4416       -- Step 4
4417       -- Check inactive terms per name
4418       -----------------------------------------------------------------------
4419       debug_info :=
4420         '(Check Invalid Terms 4) Check for inactive Terms as per Terms Name.';
4421       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4422         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4423                                       debug_info);
4424       END IF;
4425 
4426       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4427           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4428             p_invoice_rec.invoice_id,
4429             'INACTIVE TERMS',
4430             p_default_last_updated_by,
4431             p_default_last_update_login,
4432             current_calling_sequence) <> TRUE) THEN
4433         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4434           AP_IMPORT_UTILITIES_PKG.Print(
4435           AP_IMPORT_INVOICES_PKG.g_debug_switch,
4436           'insert_rejections<- '||current_calling_sequence);
4437         END IF;
4438         RAISE terms_check_failure;
4439       END IF;
4440 
4441       l_current_invoice_status := 'N';
4442     ELSE
4443        p_terms_id := l_term_id_per_name;
4444 
4445     END IF;
4446 
4447   ELSIF ((l_term_id is NOT NULL) AND
4448          ((l_term_id_per_name is NULL) OR
4449           (l_term_id_per_name is NOT NULL AND
4450            l_term_id = l_term_id_per_name))) THEN
4451 
4452     IF (not((AP_IMPORT_INVOICES_PKG.g_inv_sysdate >
4453              nvl(l_start_date_active,
4454                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate - 1))
4455         AND (AP_IMPORT_INVOICES_PKG.g_inv_sysdate <
4456              nvl(l_end_date_active,
4457                  AP_IMPORT_INVOICES_PKG.g_inv_sysdate + 1)))) THEN
4458 
4459       ----------------------------------------------------------------------
4460       -- Step 5
4461       -- Check inactive terms as per id
4462       ----------------------------------------------------------------------
4463       debug_info :=
4464         '(Check Invalid Terms 5) Check for inactive Terms as per Terms Id.';
4465       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4466         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4467                                       debug_info);
4468       END IF;
4469 
4470       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4471           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4472             p_invoice_rec.invoice_id,
4473             'INACTIVE TERMS',
4474             p_default_last_updated_by,
4475             p_default_last_update_login,
4476             current_calling_sequence) <> TRUE) THEN
4477         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4478           AP_IMPORT_UTILITIES_PKG.Print(
4479           AP_IMPORT_INVOICES_PKG.g_debug_switch,
4480           'insert_rejections<- '||current_calling_sequence);
4481         END IF;
4482         RAISE terms_check_failure;
4483       END IF;
4484 
4485       l_current_invoice_status := 'N';
4486 
4487     ELSE
4488 
4489       p_terms_id := l_term_id;
4490 
4491     END IF;
4492 
4493   END IF; -- Check Inconsistent and Inactive Terms
4494 
4495   --------------------------------------------------------------------------
4496   -- Step 6
4497   -- Check for Invoice and Goods Received Date.
4498   -- Reject the invoice if the Invoice and Goods Received Date is null
4499   -- but the terms date basis is set to Invoice Received or Goods Received.
4500   --
4501   --------------------------------------------------------------------------
4502   debug_info := '(Check Invalid Terms 6) Check for Invoice and Goods '
4503                 ||'Received Date';
4504   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4505     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4506                                   debug_info);
4507   END IF;
4508 
4509   IF (p_terms_date_basis = 'Invoice Received' AND
4510       p_invoice_rec.invoice_received_date is null) THEN
4511 
4512     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4513                       (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4514                        p_invoice_rec.invoice_id,
4515                        'DATE INVOICE RECEIVED REQ',
4516                        p_default_last_updated_by,
4517                        p_default_last_update_login,
4518                        current_calling_sequence) <> TRUE) THEN
4519       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4520         AP_IMPORT_UTILITIES_PKG.Print(
4521         AP_IMPORT_INVOICES_PKG.g_debug_switch,
4522         'insert_rejections<-'||current_calling_sequence);
4523       END IF;
4524       RAISE terms_check_failure;
4525     END IF;
4526 
4527     l_current_invoice_status := 'N';
4528 
4529   ELSIF (p_terms_date_basis = 'Goods Received' AND
4530          p_invoice_rec.goods_received_date is null) THEN
4531     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4532                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4533                       p_invoice_rec.invoice_id,
4534                       'DATE GOODS RECEIVED REQ',
4535                       p_default_last_updated_by,
4536                       p_default_last_update_login,
4537                       current_calling_sequence) <> TRUE) THEN
4538       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4539         AP_IMPORT_UTILITIES_PKG.Print(
4540         AP_IMPORT_INVOICES_PKG.g_debug_switch,
4541         'insert_rejections<-'||current_calling_sequence);
4542       END IF;
4543       RAISE terms_check_failure;
4544     END IF;
4545 
4546     l_current_invoice_status := 'N';
4547   END IF;
4548 
4549   --------------------------------------------------------------------------
4550   -- Step 7
4551   -- Derive terms date if possible
4552   --
4553   --------------------------------------------------------------------------
4554   IF (l_current_invoice_status <> 'N') THEN
4555     IF (p_invoice_rec.terms_date IS NULL) THEN
4556       IF (p_terms_date_basis = 'Invoice Received') THEN
4557         p_terms_date := p_invoice_rec.invoice_received_date;
4558       ELSIF (p_terms_date_basis = 'Goods Received') THEN
4559         p_terms_date := p_invoice_rec.goods_received_date;
4560       ELSIF (p_terms_date_basis = 'Invoice') THEN
4561         p_terms_date := p_invoice_rec.invoice_date;
4562       ELSIF (p_terms_date_basis = 'Current') THEN
4563         p_terms_date := AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
4564       ELSE
4565         p_terms_date := AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
4566       END IF;
4567     ELSE /*Bug 7635794*/
4568       p_terms_date := p_invoice_rec.terms_date; --bug 7635794
4569     END IF;
4570     p_terms_date := nvl(p_terms_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
4571   END IF;
4572 
4573  -- Bug 4115712
4574  ------------------------------------------------------------------------------
4575   -- Step 8
4576   -- For calendar based payment terms :
4577   -- Check if special calendar exists for the period
4578   -- in which the terms date falls, else fail insert.
4579   -----------------------------------------------------------------------------
4580    debug_info := '(Check Invalid Terms 8) Check calendar based payment terms';
4581 
4582    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4583       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4584                                   debug_info);
4585    END IF;
4586 
4587    --Bug:4115712
4588    IF (l_term_id IS NOT NULL)  THEN
4589     -- Bug 5448579. Calendar will be verified based on term_id
4590 
4591     --  select name
4592     --  into l_term_name
4593     --  from ap_terms
4594     --  where term_id = l_term_id;
4595 
4596     -- END IF;
4597 
4598      AP_IMPORT_UTILITIES_PKG.Check_For_Calendar_Term(
4599        P_Terms_Id         =>  l_term_id,
4600        P_Terms_Date       =>  p_terms_date,
4601        P_No_Cal           =>  l_no_calendar_exists,
4602        P_Calling_Sequence =>  'v_check_invalidate_terms');
4603 
4604      IF (l_no_calendar_exists = 'Y') THEN
4605        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4606                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4607                       p_invoice_rec.invoice_id,
4608                       'NO SPECIAL CALENDAR FOR TERMS',
4609                       p_default_last_updated_by,
4610                       p_default_last_update_login,
4611                       current_calling_sequence) <> TRUE) THEN
4612          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4613            AP_IMPORT_UTILITIES_PKG.Print(
4614            AP_IMPORT_INVOICES_PKG.g_debug_switch,
4615               'insert_rejections<-'||current_calling_sequence);
4616          END IF;
4617          RAISE terms_check_failure;
4618        END IF;
4619        l_current_invoice_status := 'N';
4620      END IF;
4621 
4622    END IF;
4623 
4624 --End bug 4115712
4625 
4626   p_current_invoice_status := l_current_invoice_status;
4627   RETURN (TRUE);
4628 
4629 EXCEPTION
4630   WHEN OTHERS THEN
4631     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4632       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4633                                     debug_info);
4634     END IF;
4635 
4636     IF (SQLCODE < 0) THEN
4637       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4638         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4639                                       SQLERRM);
4640       END IF;
4641     END IF;
4642     RETURN(FALSE);
4643 
4644 END v_check_invalid_terms;
4645 
4646 
4647 ----------------------------------------------------------------------------
4648 -- This function is used to validate several elements in the
4649 -- invoice: liability account, payment method, pay group,
4650 -- voucher num and requester.
4651 --
4652 ----------------------------------------------------------------------------
4653 FUNCTION v_check_misc_invoice_info (
4654     p_invoice_rec           IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
4655     --Bug 6509776
4656     p_set_of_books_id           IN            NUMBER,
4657     p_default_last_updated_by   IN            NUMBER,
4658     p_default_last_update_login IN            NUMBER,
4659     p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
4660     p_calling_sequence          IN            VARCHAR2)
4661 RETURN BOOLEAN IS
4662 
4663 misc_invoice_info_failure    EXCEPTION;
4664 l_valid_info                 VARCHAR2(1);
4665 l_current_invoice_status     VARCHAR2(1) := 'Y';
4666 current_calling_sequence     VARCHAR2(2000);
4667 debug_info                   VARCHAR2(500);
4668 l_invoice_count              NUMBER;
4669 l_emp_count                  NUMBER;
4670 l_chart_of_accounts_id       NUMBER;
4671 l_catsegs                    VARCHAR2(200);
4672 l_acct_type                  VARCHAR2(1);
4673 -- Bug 5448579
4674 l_valid_pay_group            PO_LOOKUP_CODES.Lookup_Code%TYPE;
4675 -- Bug 6509776
4676 l_ccid                       GL_CODE_COMBINATIONS.Code_Combination_ID%TYPE;
4677 
4678 BEGIN
4679   --
4680   -- Update the calling sequence
4681   --
4682   current_calling_sequence :=
4683    'AP_IMPORT_VALIDATION_PKG.v_check_misc_invoice_info<-'||P_calling_sequence;
4684 
4685   --
4686   -- Bug 6509776 - Adds validation for accts_pay_code_concatenated
4687   --
4688   IF (p_invoice_rec.accts_pay_code_concatenated is NOT NULL) THEN
4689     -------------------------------------------------------------------------
4690     -- Step 1 a
4691     -- Check for Liab account if entered
4692     -- Else we would default the liability account from the supplier site
4693     -- Note: No validation is done for the liab acct from the supplier, we
4694     -- just transfer the liabilty from the supplier as such. If at later
4695     -- point need be, the supplier site liab account validation logic
4696     -- can be included here.
4697     -------------------------------------------------------------------------
4698     debug_info :=
4699       '(Check Misc Invoice Info 1 a) Check for valid accts_pay_concat.';
4700      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4701        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4702                                      debug_info);
4703      END IF;
4704 
4705      -- Validate liability account concat
4706      BEGIN
4707      IF AP_IMPORT_INVOICES_PKG.g_segment_delimiter <> '-' THEN
4708         p_invoice_rec.accts_pay_code_concatenated :=
4709         TRANSLATE(p_invoice_rec.accts_pay_code_concatenated, '-',
4710                   AP_IMPORT_INVOICES_PKG.g_segment_delimiter);
4711      END IF;
4712 
4713        --Fetch chart of accounts
4714        SELECT chart_of_accounts_id
4715          INTO l_chart_of_accounts_id
4716          FROM gl_sets_of_books
4717         WHERE set_of_books_id = p_set_of_books_id;
4718 
4719          IF (fnd_flex_keyval.validate_segs
4720                       ('CREATE_COMB_NO_AT', --bugfix:3888581
4721                        'SQLGL',
4722                        'GL#',
4723                         l_chart_of_accounts_id,
4724                         p_invoice_rec.accts_pay_code_concatenated,
4725                         'V',
4726                         nvl(p_invoice_rec.gl_date,sysdate),  -- BUG 3000219
4727                         'ALL',
4728                         NULL,
4729                     -- Bug 4102147
4730                     -- '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
4731                     -- 'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
4732                         'GL_GLOBAL\nDETAIL_POSTING_ALLOWED\nI\nAPPL=SQLGL;'||
4733   'NAME=GL_CTAX_DETAIL_POSTING\nY\0GL_GLOBAL\nSUMMARY_FLAG\nI\nAPPL=SQLGL;'||
4734                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
4735                     -- End bug 4102147
4736                         NULL,
4737                         NULL,
4738                         FALSE,
4739                         FALSE,
4740                         NULL,
4741                         NULL,
4742                         NULL))  THEN
4743             l_ccid := fnd_flex_keyval.combination_id;
4744           ELSE
4745            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4746              AP_IMPORT_UTILITIES_PKG.Print(
4747              AP_IMPORT_INVOICES_PKG.g_debug_switch,
4748              '(v_check_misc_invoice_info 1 a) Invalid accts_pay_concat');
4749            END IF;
4750 
4751            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4752                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4753                   p_invoice_rec.invoice_id,
4754                   'INVALID LIABILITY ACCT',
4755                   p_default_last_updated_by,
4756                   p_default_last_update_login,
4757                   current_calling_sequence) <> TRUE) THEN
4758              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4759                AP_IMPORT_UTILITIES_PKG.Print(
4760                AP_IMPORT_INVOICES_PKG.g_debug_switch,
4761                'insert_rejections<- '||current_calling_sequence);
4762              END IF;
4763              RAISE misc_invoice_info_failure;
4764            END IF;
4765            l_current_invoice_status := 'N';
4766          END IF; -- If validate segments is TRUE
4767 
4768        SELECT account_type
4769          INTO l_acct_type
4770          FROM gl_code_combinations
4771         WHERE code_combination_id = l_ccid;
4772 
4773        IF l_acct_type <> 'L' THEN
4774          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4775            AP_IMPORT_UTILITIES_PKG.Print(
4776            AP_IMPORT_INVOICES_PKG.g_debug_switch,
4777            '(v_check_misc_invoice_info 1 a) Invalid accts_pay_concat');
4778          END IF;
4779 
4780          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4781                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4782                  p_invoice_rec.invoice_id,
4783                  'INVALID LIABILITY ACCT',
4784                  p_default_last_updated_by,
4785                  p_default_last_update_login,
4786                  current_calling_sequence) <> TRUE) THEN
4787            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4788              AP_IMPORT_UTILITIES_PKG.Print(
4789              AP_IMPORT_INVOICES_PKG.g_debug_switch,
4790              'insert_rejections<- '||current_calling_sequence);
4791            END IF;
4792            RAISE misc_invoice_info_failure;
4793          END IF;
4794 
4795          l_current_invoice_status := 'N';
4796 
4797        END IF; -- Account type is other than L
4798 
4799        -- If liab acct ccid is not null, compare both
4800        -- if not same reject as inconsistent
4801        IF p_invoice_rec.accts_pay_code_combination_id IS NOT NULL THEN
4802           IF p_invoice_rec.accts_pay_code_combination_id <> l_ccid THEN
4803              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4804                  AP_IMPORT_UTILITIES_PKG.Print(
4805                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
4806                 '(v_check_misc_invoice_info 1 a) Inconsistent accts_pay');
4807              END IF;
4808 
4809              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4810                     (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4811                       p_invoice_rec.invoice_id,
4812                       'INCONSISTENT LIAB ACCOUNT INFO',
4813                       p_default_last_updated_by,
4814                       p_default_last_update_login,
4815                       current_calling_sequence) <> TRUE) THEN
4816                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4817                   AP_IMPORT_UTILITIES_PKG.Print(
4818                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
4819                   'insert_rejections<- '||current_calling_sequence);
4820                END IF;
4821                 RAISE misc_invoice_info_failure;
4822              END IF;
4823              l_current_invoice_status := 'N';
4824            END IF;   -- END IF invoice liab ccid not equal to concat ccid
4825         ELSIF p_invoice_rec.accts_pay_code_combination_id IS NULL THEN
4826            p_invoice_rec.accts_pay_code_combination_id := l_ccid;
4827         END IF;
4828 
4829 
4830      EXCEPTION
4831        WHEN NO_DATA_FOUND Then
4832          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4833            AP_IMPORT_UTILITIES_PKG.Print(
4834            AP_IMPORT_INVOICES_PKG.g_debug_switch,
4835            '(v_check_misc_invoice_info 1 a) Invalid accts_pay_concat ');
4836          END IF;
4837 
4838          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
4839                AP_IMPORT_INVOICES_PKG.g_invoices_table,
4840                 p_invoice_rec.invoice_id,
4841                 'INVALID LIABILITY ACCT',
4842                 p_default_last_updated_by,
4843                 p_default_last_update_login,
4844                  current_calling_sequence) <> TRUE) THEN
4845            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4846              AP_IMPORT_UTILITIES_PKG.Print(
4847              AP_IMPORT_INVOICES_PKG.g_debug_switch,
4848              'insert_rejections<-'||current_calling_sequence);
4849            END IF;
4850           RAISE misc_invoice_info_failure;
4851          END IF;
4852 
4853          l_current_invoice_status := 'N';
4854 
4855      END; -- valdiate liab acct concat
4856   END IF;
4857   -- Bug 6509776
4858 
4859   IF (p_invoice_rec.accts_pay_code_combination_id is NOT NULL) THEN
4860 
4861     -------------------------------------------------------------------------
4862     -- Step 1
4863     -- Check for Liab account if entered
4864     -- Else we would default the liability account from the supplier site
4865     -- Note: No validation is done for the liab acct from the supplier, we
4866     -- just transfer the liabilty from the supplier as such. If at later
4867     -- point need be, the supplier site liab account validation logic
4868     -- can be included here.
4869     -------------------------------------------------------------------------
4870     debug_info :=
4871       '(Check Misc Invoice Info 1) Check for valid accts_pay_ccid.';
4872      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4873        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
4874                                      debug_info);
4875      END IF;
4876 
4877      -- Validate liability account information
4878      BEGIN
4879        SELECT account_type
4880          INTO l_acct_type
4881          FROM gl_code_combinations
4882         WHERE code_combination_id =
4883                 p_invoice_rec.accts_pay_code_combination_id;
4884 
4885        SELECT chart_of_accounts_id
4886          INTO l_chart_of_accounts_id
4887          FROM gl_sets_of_books
4888         WHERE set_of_books_id = p_set_of_books_id;
4889 
4890        IF l_acct_type <> 'L' THEN
4891          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4892            AP_IMPORT_UTILITIES_PKG.Print(
4893            AP_IMPORT_INVOICES_PKG.g_debug_switch,
4894            '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid');
4895          END IF;
4896 
4897          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4898                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4899                  p_invoice_rec.invoice_id,
4900                  'INVALID LIABILITY ACCT',
4901                  p_default_last_updated_by,
4902                  p_default_last_update_login,
4903                  current_calling_sequence) <> TRUE) THEN
4904            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4905              AP_IMPORT_UTILITIES_PKG.Print(
4906              AP_IMPORT_INVOICES_PKG.g_debug_switch,
4907              'insert_rejections<- '||current_calling_sequence);
4908            END IF;
4909            RAISE misc_invoice_info_failure;
4910          END IF;
4911 
4912          l_current_invoice_status := 'N';
4913 
4914        END IF; -- Account type is other than L
4915 
4916        IF fnd_flex_keyval.validate_ccid(
4917             appl_short_name  => 'SQLGL',
4918             key_flex_code    => 'GL#',
4919             structure_number => l_chart_of_accounts_id,
4920             combination_id   => p_invoice_rec.accts_pay_code_combination_id)
4921          THEN
4922          l_catsegs := fnd_flex_keyval.concatenated_values;
4923 
4924            --For BUG 3000219. CCID is to be validated with respect to
4925            --GL_DATE. Changed sysdate to p_invoice_rec.gl_date for validation
4926 
4927          IF (fnd_flex_keyval.validate_segs
4928                       ('CREATE_COMB_NO_AT', --bugfix:3888581
4929                        'SQLGL',
4930                        'GL#',
4931                         l_chart_of_accounts_id,
4932                         l_catsegs,
4933                         'V',
4934                         nvl(p_invoice_rec.gl_date,sysdate),  -- BUG 3000219
4935                         'ALL',
4936                         NULL,
4937                     -- Bug 4102147
4938                     -- '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
4939                     -- 'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
4940                          'GL_GLOBAL\nDETAIL_POSTING_ALLOWED\nI\nAPPL=SQLGL;'||
4941   'NAME=GL_CTAX_DETAIL_POSTING\nY\0GL_GLOBAL\nSUMMARY_FLAG\nI\nAPPL=SQLGL;'||
4942                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
4943                     -- End bug 4102147
4944                         NULL,
4945                         NULL,
4946                         FALSE,
4947                         FALSE,
4948                         NULL,
4949                         NULL,
4950                         NULL)<>TRUE)  THEN
4951            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4952              AP_IMPORT_UTILITIES_PKG.Print(
4953              AP_IMPORT_INVOICES_PKG.g_debug_switch,
4954              '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid');
4955            END IF;
4956 
4957            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4958                 (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4959                   p_invoice_rec.invoice_id,
4960                   'INVALID LIABILITY ACCT',
4961                   p_default_last_updated_by,
4962                   p_default_last_update_login,
4963                   current_calling_sequence) <> TRUE) THEN
4964              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4965                AP_IMPORT_UTILITIES_PKG.Print(
4966                AP_IMPORT_INVOICES_PKG.g_debug_switch,
4967                'insert_rejections<- '||current_calling_sequence);
4968              END IF;
4969              RAISE misc_invoice_info_failure;
4970            END IF;
4971 
4972            l_current_invoice_status := 'N';
4973 
4974          END IF; -- If validate segments is other than TRUE
4975 
4976        ELSE -- Validate CCID returned false
4977          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4978            AP_IMPORT_UTILITIES_PKG.Print(
4979            AP_IMPORT_INVOICES_PKG.g_debug_switch,
4980            '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid');
4981          END IF;
4982 
4983          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
4984                               (AP_IMPORT_INVOICES_PKG.g_invoices_table,
4985                                p_invoice_rec.invoice_id,
4986                                'INVALID LIABILITY ACCT',
4987                                p_default_last_updated_by,
4988                                p_default_last_update_login,
4989                                current_calling_sequence) <> TRUE) THEN
4990            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
4991              AP_IMPORT_UTILITIES_PKG.Print(
4992              AP_IMPORT_INVOICES_PKG.g_debug_switch,
4993              'insert_rejections<- '||current_calling_sequence);
4994            END IF;
4995            RAISE misc_invoice_info_failure;
4996          END IF;
4997 
4998          l_current_invoice_status := 'N';
4999 
5000        END IF; -- Validate CCID returned TRUE
5001 
5002      EXCEPTION -- Validate liability account information
5003        WHEN NO_DATA_FOUND Then
5004          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5005            AP_IMPORT_UTILITIES_PKG.Print(
5006            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5007            '(v_check_misc_invoice_info 1) Invalid accts_pay_ccid ');
5008          END IF;
5009 
5010          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5011                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5012                 p_invoice_rec.invoice_id,
5013                 'INVALID LIABILITY ACCT',
5014                 p_default_last_updated_by,
5015                 p_default_last_update_login,
5016                  current_calling_sequence) <> TRUE) THEN
5017            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5018              AP_IMPORT_UTILITIES_PKG.Print(
5019              AP_IMPORT_INVOICES_PKG.g_debug_switch,
5020              'insert_rejections<-'||current_calling_sequence);
5021            END IF;
5022           RAISE misc_invoice_info_failure;
5023          END IF;
5024 
5025          l_current_invoice_status := 'N';
5026 
5027      END; -- Validate liability account information
5028 
5029   END IF; -- liab account is not null
5030 
5031 
5032   IF (p_invoice_rec.pay_group_lookup_code is NOT NULL) THEN
5033 
5034     -------------------------------------------------------------------------
5035     -- Step 3
5036     -- Check for pay group
5037     -------------------------------------------------------------------------
5038     debug_info := '(Check Misc Invoice Info 3) Check for valid pay group';
5039     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5040       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5041                                     debug_info);
5042     END IF;
5043 
5044     -- Bug 5448579
5045     FOR i IN AP_IMPORT_INVOICES_PKG.g_pay_group_tab.First..AP_IMPORT_INVOICES_PKG.g_pay_group_tab.Last
5046     LOOP
5047       IF AP_IMPORT_INVOICES_PKG.g_pay_group_tab(i).pay_group = p_invoice_rec.pay_group_lookup_code THEN
5048         l_valid_pay_group  := AP_IMPORT_INVOICES_PKG.g_pay_group_tab(i).pay_group;
5049         EXIT;
5050       END IF;
5051     END LOOP;
5052 
5053     debug_info := 'l_valid_pay_group: '||l_valid_pay_group;
5054     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5055       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5056                                     debug_info);
5057     END IF;
5058 
5059     IF l_valid_pay_group IS NULL THEN
5060 
5061 
5062       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5063           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5064           '(v_check_misc_invoice_info 3) Invalid pay group');
5065       END IF;
5066 
5067       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5068                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5069                 p_invoice_rec.invoice_id,
5070                 'INVALID PAY GROUP',
5071                 p_default_last_updated_by,
5072                 p_default_last_update_login,
5073                  current_calling_sequence) <> TRUE) THEN
5074         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5075             AP_IMPORT_UTILITIES_PKG.Print(
5076             AP_IMPORT_INVOICES_PKG.g_debug_switch,
5077             'insert_rejections<-'||current_calling_sequence);
5078         END IF;
5079         RAISE misc_invoice_info_failure;
5080       END IF;
5081 
5082       l_current_invoice_status := 'N';
5083 
5084     END IF;
5085 
5086   END IF; -- pay group is not nul
5087    /*  -- Invalid Info
5088     BEGIN
5089       SELECT 'X'
5090         INTO l_valid_info
5091         FROM po_lookup_codes
5092        WHERE lookup_code = p_invoice_rec.pay_group_lookup_code
5093          AND lookup_type = 'PAY GROUP'
5094          AND DECODE(SIGN(NVL(inactive_date,
5095                              AP_IMPORT_INVOICES_PKG.g_inv_sysdate) -
5096                          AP_IMPORT_INVOICES_PKG.g_inv_sysdate),
5097                     -1,'','*') = '*';
5098 
5099     EXCEPTION
5100       WHEN NO_DATA_FOUND Then
5101         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5102           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5103           '(v_check_misc_invoice_info 3) Invalid pay group');
5104         END IF;
5105 
5106         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5107                AP_IMPORT_INVOICES_PKG.g_invoices_table,
5108                 p_invoice_rec.invoice_id,
5109                 'INVALID PAY GROUP',
5110                 p_default_last_updated_by,
5111                 p_default_last_update_login,
5112                  current_calling_sequence) <> TRUE) THEN
5113           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5114             AP_IMPORT_UTILITIES_PKG.Print(
5115             AP_IMPORT_INVOICES_PKG.g_debug_switch,
5116             'insert_rejections<-'||current_calling_sequence);
5117           END IF;
5118           RAISE misc_invoice_info_failure;
5119         END IF;
5120 
5121         l_current_invoice_status := 'N';
5122     END; */
5123 
5124 
5125   IF (p_invoice_rec.voucher_num IS NOT NULL) THEN
5126 
5127     --------------------------------------------------------------------------
5128     -- Step 4
5129     -- Check for duplicate voucher number.
5130     -- Retropricing: For PPA Invoices voucher num is NULL
5131     --------------------------------------------------------------------------
5132     debug_info :=
5133       '(Check Misc Invoice Info 4) Check for duplicate voucher number';
5134     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5135       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5136                                     debug_info);
5137     END IF;
5138 
5139     SELECT count(*)
5140       INTO l_invoice_count
5141       FROM ap_invoices
5142      WHERE voucher_num = p_invoice_rec.voucher_num;
5143 
5144     IF (l_invoice_count > 0) THEN
5145       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5146         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5147         '(v_check_misc_invoice_info 4) Reject: Duplicate Voucher Number');
5148       END IF;
5149 
5150       -- if data is found, an error exists
5151       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5152           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5153             p_invoice_rec.invoice_id,
5154             'DUPLICATE VOUCHER',
5155             p_default_last_updated_by,
5156             p_default_last_update_login,
5157             current_calling_sequence) <> TRUE) THEN
5158         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5159           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5160           'insert_rejections<-'||current_calling_sequence);
5161         END IF;
5162         RAISE misc_invoice_info_failure;
5163       END IF;
5164 
5165       l_current_invoice_status := 'N';
5166 
5167     END IF; -- invoice count > 0
5168 
5169   END IF; -- voucher number is not null
5170 
5171 -- Commented the below validation for Bug 5064959
5172 
5173  /* IF (p_invoice_rec.voucher_num IS NOT NULL) THEN
5174 
5175  --Bug 4158851 has added this step
5176 
5177      ------------------------------------------------------------------------------------
5178      -- Step 4.1
5179      -- Check for voucher number length (intended <= 8)
5180      ------------------------------------------------------------------------------------
5181      debug_info := '(Check Misc Invoice Info 4.1) Check for voucher number length <= 8';
5182 
5183     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5184       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5185     END IF;
5186 
5187 
5188      IF (length(p_invoice_rec.voucher_num) > 8) THEN
5189 
5190     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5191       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5192     end if;
5193 
5194          -- if data is found, an error exists
5195 
5196       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5197                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5198                         p_invoice_rec.invoice_id,
5199                         'INVALID REQUESTER',
5200                         p_default_last_updated_by,
5201                         p_default_last_update_login,
5202                         current_calling_sequence) <> TRUE) THEN
5203         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5204           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5205           'insert_rejections<-'||current_calling_sequence);
5206         END IF;
5207          RAISE misc_invoice_info_failure;
5208          END IF;
5209 
5210          l_current_invoice_status := 'N';
5211 
5212      END IF;
5213 
5214   END IF; */-- voucher number is not null
5215   --------------------------------------------------------------------------
5216   -- Step 5
5217   -- Check for valid employee
5218   --------------------------------------------------------------------------
5219   debug_info := '(Check Misc Invoice Info 5) Check for valid employee';
5220   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5221     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5222                                   debug_info);
5223   END IF;
5224 
5225   IF (p_invoice_rec.requester_id IS NOT NULL AND
5226       AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
5227 
5228     SELECT count(*)
5229       INTO l_emp_count
5230       FROM hr_employees_current_v
5231      WHERE employee_id = p_invoice_rec.requester_id;
5232 
5233     IF l_emp_count = 0 THEN
5234 
5235       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5236                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5237                         p_invoice_rec.invoice_id,
5238                         'INVALID REQUESTER',
5239                         p_default_last_updated_by,
5240                         p_default_last_update_login,
5241                         current_calling_sequence) <> TRUE) THEN
5242         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5243           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5244           'insert_rejections<-'||current_calling_sequence);
5245         END IF;
5246 
5247         RAISE misc_invoice_info_failure;
5248       END IF;
5249 
5250       l_current_invoice_status := 'N';
5251 
5252     END IF; -- employee count is 0
5253   END IF; -- requester id is not null
5254 
5255   p_current_invoice_status := l_current_invoice_status;
5256 
5257   RETURN (TRUE);
5258 
5259 EXCEPTION
5260   WHEN OTHERS THEN
5261     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5262       AP_IMPORT_UTILITIES_PKG.Print(
5263       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5264     END IF;
5265 
5266     IF (SQLCODE < 0) then
5267       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5268         AP_IMPORT_UTILITIES_PKG.Print(
5269         AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
5270       END IF;
5271     END IF;
5272 
5273     RETURN(FALSE);
5274 
5275 END v_check_misc_invoice_info;
5276 
5277 ----------------------------------------------------------------------------
5278 -- This function is used to validate the Legal Entity information of the
5279 -- invoice that is being imported.
5280 --
5281 ----------------------------------------------------------------------------
5282 FUNCTION v_check_Legal_Entity_info (
5283     p_invoice_rec               IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
5284     p_set_of_books_id           IN            NUMBER,
5285     p_default_last_updated_by   IN            NUMBER,
5286     p_default_last_update_login IN            NUMBER,
5287     p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
5288     p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
5289 IS
5290 
5291 le_invoice_info_failure         EXCEPTION;
5292 l_valid_info                    VARCHAR2(1);
5293 l_current_invoice_status        VARCHAR2(1) := 'Y';
5294 current_calling_sequence        VARCHAR2(2000);
5295 debug_info                      VARCHAR2(500);
5296 
5297 l_ptop_le_info                  XLE_BUSINESSINFO_GRP.ptop_le_rec;
5298 l_le_return_status              varchar2(1);
5299 l_msg_data                      varchar2(1000);
5300 l_bill_to_location_id           NUMBER(15);
5301 l_supp_site_liab_ccid           NUMBER(15);
5302 l_ccid_to_api                   NUMBER(15);
5303 l_valid_le                      VARCHAR2(100);
5304 
5305 BEGIN
5306   --
5307   -- Update the calling sequence
5308   --
5309   current_calling_sequence :=
5310    'AP_IMPORT_VALIDATION_PKG.v_check_legal_entity_info<-'||P_calling_sequence;
5311 
5312      IF (p_invoice_rec.legal_entity_id IS NOT NULL) THEN
5313          ----------------------------------------------------------------------
5314          -- Step 1
5315          -- LE ID is provided. Validate if it is a valid LE.
5316          -----------------------------------------------------------------------
5317          debug_info :=
5318                '(Check Legal Entity Info 1) Check Valid LE ID';
5319          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5320             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5321                                      debug_info);
5322          END IF;
5323 
5324          XLE_UTILITIES_GRP.IsLegalEntity_LEID
5325                            (l_le_return_status,
5326                             l_msg_data,
5327                             p_invoice_rec.legal_entity_id,
5328                             l_valid_le);
5329 
5330          IF l_le_return_status = FND_API.G_RET_STS_SUCCESS THEN
5331             IF l_valid_le = FND_API.G_FALSE THEN
5332               ------------------------------------------------------------------
5333               -- Step 1.1
5334               -- Invalid LE ID Case
5335               --
5336               ------------------------------------------------------------------
5337               debug_info :=
5338                          '(Check Legal Entity Info 1.1) InValid LE ID Flow';
5339               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5340                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5341                                             debug_info);
5342               END IF;
5343               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5344                    (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5345                      p_invoice_rec.invoice_id,
5346                      'INVALID LEGAL ENTITY',
5347                      p_default_last_updated_by,
5348                      p_default_last_update_login,
5349                      current_calling_sequence) <> TRUE) THEN
5350                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5351                      AP_IMPORT_UTILITIES_PKG.Print(
5352                             AP_IMPORT_INVOICES_PKG.g_debug_switch,
5353                            'insert_rejections<- '||current_calling_sequence);
5354                   END IF;
5355                   l_current_invoice_status := 'N';
5356                   RAISE le_invoice_info_failure;
5357               END IF;
5358             END IF;
5359          END IF;
5360      END IF;
5361 
5362      IF ((p_invoice_rec.cust_registration_code IS NOT NULL) AND
5363         (p_invoice_rec.cust_registration_number IS NOT NULL)) OR
5364          /* Bug 4516037. Added the following condition */
5365          (p_invoice_rec.legal_entity_id IS NULL) THEN
5366          -----------------------------------------------------------------------
5367          -- Step 2
5368          -- This case the registration code and the number are provided
5369          -- Call the LE API to validate the registration code and number to
5370          -- get the right LE information.
5371          --
5372          -----------------------------------------------------------------------
5373          debug_info :=
5374                '(Check Legal Entity Info 2) Check for reg code/number and Get LE.';
5375          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5376             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5377                                      debug_info);
5378          END IF;
5379          -----------------------------------------------------------------------
5380          -- Step 2.1
5381          -- Get Bill TO Location ID from Supplier Site
5382          --
5383          -----------------------------------------------------------------------
5384 
5385          -- Bug 5518886 . Added the following condition If
5386          IF p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST' THEN
5387 
5388            debug_info :=
5389                '(Check Legal Entity Info 2.1) Get Bill TO Location ID';
5390            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5391              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5392                                       debug_info);
5393            END IF;
5394 
5395 
5396            BEGIN
5397              SELECT bill_to_location_id,
5398                     accts_pay_code_combination_id
5399              INTO   l_bill_to_location_id,
5400                     l_supp_site_liab_ccid
5401              FROM   po_vendor_sites
5402              WHERE  vendor_site_id = p_invoice_rec.vendor_site_id;
5403 
5404              l_ccid_to_api := NVL(p_invoice_rec.accts_pay_code_combination_id,
5405                                 l_supp_site_liab_ccid);
5406            EXCEPTION
5407              WHEN OTHERS THEN
5408                l_bill_to_location_id := NULL;
5409                l_ccid_to_api := p_invoice_rec.accts_pay_code_combination_id;
5410            END;
5411 
5412          ELSE
5413 
5414            debug_info :=
5415                '(Check Legal Entity Info 2.1) For Payment Request Legal Entity will '
5416                || 'based on interface accts_pay_code_combination_id ';
5417            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5418              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5419                                       debug_info);
5420            END IF;
5421 
5422            l_ccid_to_api := p_invoice_rec.accts_pay_code_combination_id;
5423 
5424          END IF;
5425 
5426          ----------------------------------------------------------------------
5427          -- Step 2.2
5428          -- Call the LE API
5429          --
5430          ----------------------------------------------------------------------
5431          debug_info :=
5432                '(Check Legal Entity Info 2.2) Call LE API';
5433          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5434             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5435                                      debug_info);
5436          END IF;
5437 
5438          XLE_BUSINESSINFO_GRP.Get_PurchasetoPay_Info
5439                               (l_le_return_status,
5440                                l_msg_data,
5441                                p_invoice_rec.cust_registration_code,
5442                                p_invoice_rec.cust_registration_number,
5443                                l_bill_to_location_id,
5444                                l_ccid_to_api,
5445                                p_invoice_rec.org_id,
5446                                l_ptop_le_info);
5447          IF (l_le_return_status = FND_API.G_RET_STS_SUCCESS) THEN
5448             --------------------------------------------------------------------
5449             -- Step 2.3
5450             -- Valid LE Returned by the API.
5451             --
5452             -------------------------------------------------------------------
5453             debug_info :=
5454                        '(Check Legal Entity Info 2.3) Valid LE Flow';
5455             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5456                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5457                                             debug_info);
5458             END IF;
5459             IF p_invoice_rec.legal_entity_id IS NOT NULL THEN
5460                IF p_invoice_rec.legal_entity_id <>
5461                   l_ptop_le_info.legal_entity_id THEN
5462                   -------------------------------------------------------------
5463                   -- Step 2.4
5464                   -- Inconsistent LE Info
5465                   --
5466                   -------------------------------------------------------------
5467                   debug_info :=
5468                              '(Check Legal Entity Info 2.4) Inconsistent LE Info';
5469                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5470                       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5471                                                  debug_info);
5472                   END IF;
5473                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5474                      (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5475                             p_invoice_rec.invoice_id,
5476                             'INCONSISTENT LE INFO',
5477                             p_default_last_updated_by,
5478                             p_default_last_update_login,
5479                             current_calling_sequence) <> TRUE) THEN
5480                      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5481                          AP_IMPORT_UTILITIES_PKG.Print(
5482                            AP_IMPORT_INVOICES_PKG.g_debug_switch,
5483                           'insert_rejections<- '||current_calling_sequence);
5484                      END IF;
5485                      l_current_invoice_status := 'N';
5486                      RAISE le_invoice_info_failure;
5487                   END IF;
5488                END IF;
5489             END IF;
5490             p_invoice_rec.legal_entity_id := l_ptop_le_info.legal_entity_id;
5491             /* Bug 4516037. Added the following debug info for printing
5492                legal entity id */
5493             debug_info :=
5494                      '(Check Legal Entity Info 2.4a) Legal Entity ID: '||
5495                        p_invoice_rec.legal_entity_id;
5496             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5497               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5498                                            debug_info);
5499             END IF;
5500 
5501 
5502 
5503 
5504 
5505 
5506          ELSE
5507             -------------------------------------------------------------------
5508             -- Step 2.5
5509             -- Invalid LE Case
5510             --
5511             -------------------------------------------------------------------
5512             debug_info :=
5513                        '(Check Legal Entity Info 2.5) InValid LE Flow';
5514             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5515                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5516                                             debug_info);
5517             END IF;
5518             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5519                  (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5520                    p_invoice_rec.invoice_id,
5521                    'INVALID LEGAL ENTITY',
5522                    p_default_last_updated_by,
5523                    p_default_last_update_login,
5524                    current_calling_sequence) <> TRUE) THEN
5525                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5526                    AP_IMPORT_UTILITIES_PKG.Print(
5527                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
5528                          'insert_rejections<- '||current_calling_sequence);
5529                 END IF;
5530                 l_current_invoice_status := 'N';
5531                 RAISE le_invoice_info_failure;
5532             END IF;
5533          END IF;
5534      END IF;
5535 
5536   p_current_invoice_status := l_current_invoice_status;
5537   RETURN (TRUE);
5538 EXCEPTION
5539   WHEN OTHERS THEN
5540     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5541       AP_IMPORT_UTILITIES_PKG.Print(
5542       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5543     END IF;
5544 
5545     IF (SQLCODE < 0) then
5546       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5547         AP_IMPORT_UTILITIES_PKG.Print(
5548         AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
5549       END IF;
5550     END IF;
5551     RETURN(FALSE);
5552 END v_check_Legal_Entity_info;
5553 
5554 ------------------------------------------------------------------------------
5555 -- This function is used to validate payment currency.
5556 --
5557 ------------------------------------------------------------------------------
5558 FUNCTION v_check_invalid_pay_curr (
5559          p_invoice_rec            IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
5560          p_pay_currency_code            OUT NOCOPY VARCHAR2,
5561          p_payment_cross_rate_date      OUT NOCOPY DATE,
5562          p_payment_cross_rate           OUT NOCOPY NUMBER,
5563          p_payment_cross_rate_type      OUT NOCOPY VARCHAR2,
5564          p_default_last_updated_by   IN            NUMBER,
5565          p_default_last_update_login IN            NUMBER,
5566          p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
5567          p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
5568 IS
5569 
5570 invalid_pay_curr_code_failure    EXCEPTION;
5571 l_current_invoice_status         VARCHAR2(1) := 'Y';
5572 l_start_date_active              DATE;
5573 l_end_date_active                DATE;
5574 l_payment_cross_rate             AP_INVOICES_INTERFACE.payment_cross_rate%TYPE;
5575 l_warning                        VARCHAR2(240);
5576 current_calling_sequence         VARCHAR2(2000);
5577 debug_info                       VARCHAR2(500);
5578 
5579 l_fnd_currency_table             AP_IMPORT_INVOICES_PKG.Fnd_Currency_Tab_Type;
5580 l_valid_pay_currency             FND_CURRENCIES.Currency_Code%TYPE;
5581 
5582 BEGIN
5583   --
5584   -- Update the calling sequence
5585   --
5586   current_calling_sequence :=
5587    'AP_IMPORT_VALIDATION_PKG.v_check_invalid_pay_curr<-'||P_calling_sequence;
5588 
5589   -- Bug 5448579
5590   debug_info := '(Check Invalid Pay Currency 0)  Calling Caching Function for Currency';
5591   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
5592       AP_IMPORT_UTILITIES_PKG.Print(
5593         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
5594   END IF;
5595   IF (AP_IMPORT_UTILITIES_PKG.Cache_Fnd_Currency (
5596            P_Fnd_Currency_Table   => l_fnd_currency_table,
5597            P_Calling_Sequence     => current_calling_sequence ) <> TRUE) THEN
5598     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
5599               AP_IMPORT_UTILITIES_PKG.Print(
5600                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
5601                'Cache_Fnd_Currency <-'||current_calling_sequence);
5602     END IF;
5603     Raise invalid_pay_curr_code_failure;
5604   END IF;
5605 
5606   IF (p_invoice_rec.payment_currency_code IS NOT NULL) THEN
5607     -------------------------------------------------------------------------
5608     -- Step 1
5609     -- Check if the payment currency is inactive. If no data found then
5610     -- payment currency is invalid and will be handled in EXCEPTION clause
5611     -------------------------------------------------------------------------
5612 
5613     /*SELECT start_date_active, end_date_active
5614       INTO l_start_date_active, l_end_date_active
5615       FROM fnd_currencies
5616      WHERE currency_code = p_invoice_rec.payment_currency_code; */
5617 
5618      -- Bug 5448579
5619     FOR i IN l_fnd_currency_table.First..l_fnd_currency_table.Last LOOP
5620       IF l_fnd_currency_table(i).currency_code = p_invoice_rec.payment_currency_code THEN
5621         l_valid_pay_currency  := l_fnd_currency_table(i).currency_code;
5622         l_start_date_active   := l_fnd_currency_table(i).start_date_active;
5623         l_end_date_active     := l_fnd_currency_table(i).end_date_active;
5624         EXIT;
5625       END IF;
5626     END LOOP;
5627 
5628     debug_info := 'l_valid_pay_currency: '||l_valid_pay_currency;
5629     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5630       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5631                                     debug_info);
5632     END IF;
5633 
5634     IF l_valid_pay_currency IS NOT NULL THEN
5635       IF ((trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate) <
5636         nvl(l_start_date_active,
5637             trunc(AP_IMPORT_INVOICES_PKG.g_inv_sysdate))) OR
5638         (AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
5639          nvl(l_end_date_active, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))) THEN
5640 
5641         debug_info := '(Check Payment Currency Code 1) Check for Inactive '
5642                     ||'Payment Currency Code.';
5643         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5644           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5645                                       debug_info);
5646         END IF;
5647 
5648         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5649           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5650             p_invoice_rec.invoice_id,
5651             'INACTIVE PAY CURR CODE',
5652             p_default_last_updated_by,
5653             p_default_last_update_login,
5654             current_calling_sequence) <> TRUE) THEN
5655           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5656             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5657             'insert_rejections<-'||current_calling_sequence);
5658           END IF;
5659           RAISE invalid_pay_curr_code_failure;
5660         END IF;
5661 
5662         l_current_invoice_status := 'N';
5663       END IF; -- Test of inactive payment currency code
5664     ELSE
5665       debug_info := '(Check Payment Currency Code 1.1) Check for Inactive '
5666                     ||'Payment Currency Code.';
5667       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5668           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5669                                       debug_info);
5670       END IF;
5671 
5672       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5673           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5674             p_invoice_rec.invoice_id,
5675             'INACTIVE PAY CURR CODE',
5676             p_default_last_updated_by,
5677             p_default_last_update_login,
5678             current_calling_sequence) <> TRUE) THEN
5679          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5680             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5681             'insert_rejections <-'||current_calling_sequence);
5682          END IF;
5683          RAISE invalid_pay_curr_code_failure;
5684        END IF;
5685 
5686     END IF;
5687     --------------------------------------------------------------------------
5688     -- Step 2
5689     -- Check if the payment cross rate date is null. If yes, assign the
5690     -- invoice_date to it.
5691     --------------------------------------------------------------------------
5692     IF (p_invoice_rec.payment_cross_rate_date IS NULL) THEN
5693       p_payment_cross_rate_date := p_invoice_rec.invoice_date;
5694     ELSE
5695       p_payment_cross_rate_date := p_invoice_rec.payment_cross_rate_date;
5696     END IF;
5697 
5698     --------------------------------------------------------------------------
5699     -- Step 3
5700     -- Check if the invoice and payment currency have fixed rate relationship.
5701     --------------------------------------------------------------------------
5702     IF ( p_invoice_rec.payment_currency_code <>
5703              p_invoice_rec.invoice_currency_code) THEN
5704 
5705       IF ( gl_currency_api.is_fixed_rate(
5706                p_invoice_rec.invoice_currency_code,
5707                p_invoice_rec.payment_currency_code,
5708                p_payment_cross_rate_date) <> 'Y' ) THEN
5709 
5710         debug_info := '(Check Payment Currency Code 3.1) Check for fixed '
5711                       ||'payment cross rate.';
5712         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5713           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5714                                         debug_info);
5715         END IF;
5716 
5717         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
5718                 AP_IMPORT_INVOICES_PKG.g_invoices_table,
5719                  p_invoice_rec.invoice_id,
5720                  'PAY X RATE NOT FIXED',
5721                  p_default_last_updated_by,
5722                  p_default_last_update_login,
5723                  current_calling_sequence) <> TRUE) THEN
5724           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5725             AP_IMPORT_UTILITIES_PKG.Print(
5726                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
5727                 'insert_rejections<-'||current_calling_sequence);
5728           END IF;
5729           RAISE invalid_pay_curr_code_failure;
5730         END IF;
5731 
5732         l_current_invoice_status := 'N';
5733       ELSE
5734         p_payment_cross_rate_type := 'EMU FIXED';
5735         l_payment_cross_rate := ap_utilities_pkg.get_exchange_rate(
5736                                     p_invoice_rec.invoice_currency_code,
5737                                     p_invoice_rec.payment_currency_code,
5738                                     p_payment_cross_rate_type,
5739                                     p_payment_cross_rate_date,
5740                                     current_calling_sequence);
5741         debug_info := '(Check Payment Currency Code 3.2) Check for fixed '
5742                       ||' and get payment cross rate.';
5743         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5744           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5745                                         debug_info);
5746         END IF;
5747 
5748         IF ( (l_payment_cross_rate <> p_invoice_rec.payment_cross_rate) AND
5749              (p_invoice_rec.payment_cross_rate IS NOT NULL)) THEN
5750           BEGIN
5751             SELECT  description
5752               INTO  l_warning
5753               FROM  ap_lookup_codes
5754              WHERE  lookup_type = 'REJECT CODE'
5755                AND  lookup_code = 'PAY RATE OVERWRITTEN';
5756              debug_info := '(Check Payment Currency Code 3.3) Check for fixed '
5757                           || l_warning;
5758              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5759                AP_IMPORT_UTILITIES_PKG.Print(
5760                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
5761              END IF;
5762           EXCEPTION WHEN no_data_found THEN
5763             NULL;
5764           END;
5765         END IF;
5766         p_payment_cross_rate := l_payment_cross_rate;
5767       END IF; -- end of gl_is_fix rate api call
5768     ELSE
5769 
5770       -- pay_curr_code = inv_curr_code case
5771       debug_info := '(Check Payment Currency Code 3.3) Check for fixed '
5772                       ||' pay_currency_code = inv_currency_code';
5773       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5774           AP_IMPORT_UTILITIES_PKG.Print(
5775               AP_IMPORT_INVOICES_PKG.g_debug_switch,
5776               debug_info);
5777       END IF;
5778 
5779       p_pay_currency_code := p_invoice_rec.invoice_currency_code;
5780       IF (p_invoice_rec.payment_cross_rate_date IS NULL) THEN
5781         p_payment_cross_rate_date := p_invoice_rec.invoice_date;
5782       END IF;
5783 
5784       p_payment_cross_rate := 1;
5785       p_payment_cross_rate_type := NULL;
5786 
5787     END IF; -- Payment currency code is other than invoice currency code
5788 
5789   ELSIF (p_invoice_rec.payment_currency_code is NULL ) THEN
5790 
5791     p_pay_currency_code := p_invoice_rec.invoice_currency_code;
5792     IF (p_invoice_rec.payment_cross_rate_date IS NULL) THEN
5793       p_payment_cross_rate_date := p_invoice_rec.invoice_date;
5794     END IF;
5795 
5796     p_payment_cross_rate := 1;
5797     p_payment_cross_rate_type := NULL;
5798 
5799   END IF; -- endif for payment currency code not null
5800 
5801   p_current_invoice_status := l_current_invoice_status;
5802   RETURN (TRUE);
5803 
5804 EXCEPTION
5805   WHEN no_data_found THEN
5806 
5807     -------------------------------------------------------------------------
5808     -- Step 4
5809     -- Check for Invalid Payment Currency Code.
5810     -------------------------------------------------------------------------
5811     debug_info := '(Check Invoice Currency Code 4) Check for Invalid Invoice'
5812                   ||' Currency Code.';
5813     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5814       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5815                                     debug_info);
5816     END IF;
5817 
5818     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
5819           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
5820             p_invoice_rec.invoice_id,
5821             'INVALID PAY CURR CODE',
5822             p_default_last_updated_by,
5823             p_default_last_update_login,
5824             current_calling_sequence) <> TRUE) THEN
5825       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5826         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5827         'insert_rejections<-'||current_calling_sequence);
5828       END IF;
5829       RAISE invalid_pay_curr_code_failure;
5830     END IF;
5831 
5832     l_current_invoice_status := 'N';
5833     p_current_invoice_status := l_current_invoice_status;
5834     RETURN (TRUE);
5835 
5836   WHEN OTHERS THEN
5837     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5838       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5839                                     debug_info);
5840     END IF;
5841 
5842     IF (SQLCODE < 0) then
5843       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5844         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5845                                       SQLERRM);
5846       END IF;
5847     END IF;
5848     RETURN(FALSE);
5849 
5850 END v_check_invalid_pay_curr;
5851 
5852 -----------------------------------------------------------------------------
5853 -- This function is used to validate prepayment information for
5854 -- application.
5855 -----------------------------------------------------------------------------
5856 
5857 FUNCTION v_check_prepay_info(
5858           p_invoice_rec               IN OUT NOCOPY
5859                                       AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
5860           p_base_currency_code        IN            VARCHAR2,
5861           p_prepay_period_name        IN OUT NOCOPY VARCHAR2,
5862 	  p_prepay_invoice_id	      OUT NOCOPY    NUMBER,
5863 	  p_prepay_case_name	      OUT NOCOPY    VARCHAR2,
5864           p_request_id                IN            NUMBER,
5865           p_default_last_updated_by   IN            NUMBER,
5866           p_default_last_update_login IN            NUMBER,
5867           p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
5868           p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
5869 IS
5870 
5871 l_current_invoice_status        VARCHAR2(1);
5872 l_reject_code                   VARCHAR2(30);
5873 current_calling_sequence        VARCHAR2(2000);
5874 debug_info                      VARCHAR2(500);
5875 check_prepay_failure            EXCEPTION;
5876 l_count_lines_matched	        NUMBER;
5877 
5878 BEGIN
5879   --
5880   current_calling_sequence :=  'AP_IMPORT_VALIDATION_PKG.v_check_prepay_info<-'
5881                                 ||P_calling_sequence;
5882 
5883   l_count_lines_matched  := 0;
5884 
5885   --Contract Payments: Added the below IF condition so that we reject the invoices
5886   --which are of type 'PREPAYMENT' and have provided the prepayment application
5887   --information too.
5888 
5889   IF (((p_invoice_rec.prepay_num          IS NOT NULL) OR
5890        (p_invoice_rec.prepay_line_num     IS NOT NULL) OR
5891        (p_invoice_rec.prepay_apply_amount IS NOT NULL) OR
5892        (p_invoice_rec.prepay_gl_date      IS NOT NULL) OR
5893        (p_invoice_rec.invoice_includes_prepay_flag IS NOT NULL)) AND
5894       p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT')THEN
5895 
5896        debug_info := '(Check Prepayment Info 1) Check if it is a Prepayment Invoice';
5897 
5898        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5899          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5900 		                                    debug_info);
5901        END IF;
5902 
5903        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections (
5904                  AP_IMPORT_INVOICES_PKG.g_invoices_table,
5905 		 p_invoice_rec.invoice_id,
5906 		 'INCONSISTENT PREPAY APPL INFO',
5907 		 p_default_last_updated_by,
5908 		 p_default_last_update_login,
5909 		 current_calling_sequence) <> TRUE) THEN
5910 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5911 	      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5912 			           'insert_rejections<-'||current_calling_sequence);
5913 	   END IF;
5914 	   RAISE check_prepay_failure;
5915        END IF;
5916 
5917        l_current_invoice_status := 'N';
5918 
5919   END IF;
5920 
5921   --Contract Payments: If the prepayment invoice is matched to financing pay items,
5922   --reject the invoice, as manual recoupment is not allowed.
5923   IF ((p_invoice_rec.prepay_num IS NOT NULL) AND
5924       (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT')) THEN
5925 
5926      debug_info := '(Check Prepayment Info 2) Check if it is a Prepayment Invoice matched'||
5927      				' to a complex works po';
5928 
5929     -- debug_info := 'p_invoice_rec.prepay_num , p_invoice_rec.org_id '|| p_invoice_rec.prepay_num||','||p_invoice_rec.org_id;
5930 
5931      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5932          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5933                                                debug_info);
5934      END IF;
5935 
5936 
5937      BEGIN
5938 
5939         SELECT count(*)
5940         INTO l_count_lines_matched
5941         FROM ap_invoice_lines ail,
5942           ap_invoices ai,
5943           po_line_locations pll
5944         WHERE ai.invoice_num = p_invoice_rec.prepay_num
5945         AND ai.org_id = p_invoice_rec.org_id
5946         AND ail.invoice_id = ai.invoice_id
5947         AND ail.po_line_location_id = pll.line_location_id
5948         AND pll.shipment_type = 'PREPAYMENT';
5949 
5950      EXCEPTION WHEN OTHERS THEN
5951        debug_info := '(Check Prepayment Info 2.1) In others exception and the error is '||sqlerrm;
5952        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5953              AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5954 	                                            debug_info);
5955        END IF;
5956 
5957 
5958      END ;
5959 
5960 
5961      IF (l_count_lines_matched > 0) THEN
5962 
5963 	debug_info := 'Reject as Cannot manually recoup ';
5964         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5965          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5966 		                                    debug_info);
5967         END IF;
5968 
5969         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections (
5970                  AP_IMPORT_INVOICES_PKG.g_invoices_table,
5971 		 p_invoice_rec.invoice_id,
5972 		 'CANNOT MANUALLY RECOUP',
5973 		 p_default_last_updated_by,
5974 		 p_default_last_update_login,
5975 		 current_calling_sequence) <> TRUE) THEN
5976 	    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
5977 	       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
5978 			           'insert_rejections<-'||current_calling_sequence);
5979 	    END IF;
5980  	    RAISE check_prepay_failure;
5981         END IF;
5982 
5983         l_current_invoice_status := 'N';
5984 
5985      END IF;
5986 
5987   END IF;
5988 
5989 
5990   IF (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT') THEN
5991 
5992      IF NOT ((p_invoice_rec.prepay_num          IS NULL) AND
5993              (p_invoice_rec.prepay_line_num     IS NULL) AND
5994              (p_invoice_rec.prepay_apply_amount IS NULL)
5995 	    ) THEN
5996        --------------------------------------------------------------------------
5997        -- Step 1
5998        -- Check Prepayment Info.
5999        --------------------------------------------------------------------------
6000 
6001        debug_info := '(Check Prepayment Info 1) Call Check Prepayment Function.';
6002 
6003        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6004          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6005                                     debug_info);
6006        END IF;
6007        --
6008        l_reject_code := AP_PREPAY_PKG.check_prepay_info_import(
6009       			    	p_invoice_rec.prepay_num,
6010           			p_invoice_rec.prepay_line_num,
6011           			p_invoice_rec.prepay_apply_amount,
6012           			p_invoice_rec.invoice_amount,
6013           			p_invoice_rec.prepay_gl_date,
6014           			p_prepay_period_name,
6015           			p_invoice_rec.vendor_id,
6016           			p_invoice_rec.invoice_includes_prepay_flag,
6017           			p_invoice_rec.invoice_id,
6018           			p_invoice_rec.source,
6019           			p_invoice_rec.apply_advances_flag,
6020           			p_invoice_rec.invoice_date,
6021           			p_base_currency_code,
6022           			p_invoice_rec.invoice_currency_code,
6023           			p_invoice_rec.payment_currency_code,
6024           			current_calling_sequence,
6025           			p_request_id,
6026           			p_prepay_case_name,
6027           			p_prepay_invoice_id,
6028 				p_invoice_rec.invoice_type_lookup_code);  -- Bug 7004765;
6029     	--
6030     	-- show input/output values (only if debug_switch = 'Y')
6031 
6032     	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6033       		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6034           	'------------------> prepay_num = '|| p_invoice_rec.prepay_num
6035         	||' prepay_line_num  = '||to_char(p_invoice_rec.prepay_line_num)
6036         	||' prepay_apply_amount = '||to_char(p_invoice_rec.prepay_apply_amount)
6037         	||' invoice_amount  = '||to_char(p_invoice_rec.invoice_amount)
6038         	||' prepay_gl_date  = '||to_char(p_invoice_rec.prepay_gl_date)
6039         	||' prepay_period_name  = '|| NULL
6040         	||' vendor_id    = '||to_char(p_invoice_rec.vendor_id)
6041         	||' base_currency_code = '||p_base_currency_code
6042         	||' invoice_currency_code  = '||p_invoice_rec.invoice_currency_code
6043         	||' payment_currency_code  = '||p_invoice_rec.payment_currency_code);
6044     	END IF;
6045 
6046     	IF (l_reject_code IS NOT NULL) THEN
6047 
6048       	   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
6049                   AP_IMPORT_INVOICES_PKG.g_invoices_table,
6050           	  p_invoice_rec.invoice_id,
6051                   l_reject_code,
6052                   p_default_last_updated_by,
6053                   p_default_last_update_login,
6054                   current_calling_sequence) <> TRUE) THEN
6055                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6056           	  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6057           	  'insert_rejections<-' ||current_calling_sequence);
6058                END IF;
6059                RAISE check_prepay_failure;
6060            END IF;
6061 
6062            l_current_invoice_status := 'N';
6063 
6064         END IF;  -- reject code is not null
6065 
6066      END IF; -- If not prepayment information is available
6067 
6068   END IF; --p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT'
6069 
6070   p_current_invoice_status := l_current_invoice_status;
6071 
6072   RETURN(TRUE);
6073 
6074 EXCEPTION
6075   WHEN OTHERS THEN
6076     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6077       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6078                                     debug_info);
6079     END IF;
6080 
6081     IF (SQLCODE < 0) then
6082       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6083         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6084                                       SQLERRM);
6085       END IF;
6086     END IF;
6087     RETURN(FALSE);
6088 
6089 END v_check_prepay_info;
6090 
6091 
6092 -----------------------------------------------------------------------------
6093 -- This function is used to validate information provided to
6094 -- calculate rate based on base amount.
6095 --
6096 -----------------------------------------------------------------------------
6097 FUNCTION v_check_no_xrate_base_amount (
6098          p_invoice_rec               IN
6099              AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
6100          p_base_currency_code        IN            VARCHAR2,
6101          p_multi_currency_flag       IN            VARCHAR2,
6102          p_calc_user_xrate           IN            VARCHAR2,
6103          p_default_last_updated_by   IN            NUMBER,
6104          p_default_last_update_login IN            NUMBER,
6105      p_invoice_base_amount          OUT NOCOPY NUMBER,
6106          p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
6107          p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
6108 IS
6109 
6110 no_xrate_base_amount_failure    EXCEPTION;
6111 l_current_invoice_status    VARCHAR2(1) := 'Y';
6112 current_calling_sequence      VARCHAR2(2000);
6113 debug_info           VARCHAR2(500);
6114 
6115 BEGIN
6116 
6117   -- Update the calling sequence
6118   current_calling_sequence :=
6119     'AP_IMPORT_VALIDATION_PKG.v_check_no_xrate_base_amount<-'
6120      ||P_calling_sequence;
6121 
6122   -------------------------------------------------------------------------
6123   -- Step 1 - Check for invalid no_xrate_base_amount
6124   -------------------------------------------------------------------------
6125   debug_info := '(Check No Xrate Base Amount 1) Is Xrate_Base_Amount invalid?';
6126   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6127      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6128                    debug_info);
6129   END IF;
6130 
6131   IF (nvl(p_multi_currency_flag,'N') = 'Y') AND
6132          (p_base_currency_code <> p_invoice_rec.invoice_currency_code) THEN
6133 
6134     IF ((p_calc_user_xrate <> 'Y') AND
6135         (p_invoice_rec.no_xrate_base_amount IS NOT NULL)) THEN
6136       debug_info := 'Trying to reject due to no_x_Curr';
6137       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6138         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6139                       debug_info);
6140       END IF;
6141 
6142       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6143             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6144               p_invoice_rec.invoice_id,
6145               'BASE AMOUNT NOT ALLOWED',
6146               p_default_last_updated_by,
6147               p_default_last_update_login,
6148               current_calling_sequence) <> TRUE) THEN
6149         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6150           AP_IMPORT_UTILITIES_PKG.Print(
6151           AP_IMPORT_INVOICES_PKG.g_debug_switch,
6152           'insert_rejections<-'||current_calling_sequence);
6153         END IF;
6154         RAISE no_xrate_base_amount_failure;
6155       END IF;
6156 
6157       l_current_invoice_status := 'N';
6158 
6159     ELSIF (p_calc_user_xrate = 'Y') AND
6160           ((p_invoice_rec.exchange_rate_type <> 'User') AND
6161            (p_invoice_rec.no_xrate_base_amount IS NOT NULL)) THEN
6162 
6163       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6164             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6165               p_invoice_rec.invoice_id,
6166               'INVALID EXCH RATE TYPE',
6167               p_default_last_updated_by,
6168               p_default_last_update_login,
6169               current_calling_sequence) <> TRUE) THEN
6170         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6171           AP_IMPORT_UTILITIES_PKG.Print(
6172           AP_IMPORT_INVOICES_PKG.g_debug_switch,
6173           'insert_rejections<-'||current_calling_sequence);
6174         END IF;
6175         RAISE no_xrate_base_amount_failure;
6176       END IF;
6177 
6178       l_current_invoice_status := 'N';
6179 
6180     ELSIF (p_calc_user_xrate = 'Y') AND
6181           ((p_invoice_rec.exchange_rate_type = 'User') AND
6182            (p_invoice_rec.no_xrate_base_amount IS NOT NULL) AND
6183            (p_invoice_rec.invoice_amount IS NOT NULL) AND
6184            (p_invoice_rec.exchange_rate is NOT NULL)) THEN
6185 
6186       IF (ap_utilities_pkg.ap_round_currency(
6187            (p_invoice_rec.invoice_amount*p_invoice_rec.exchange_rate),
6188            p_base_currency_code) <> p_invoice_rec.no_xrate_base_amount)
6189         THEN
6190 
6191         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6192             (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6193               p_invoice_rec.invoice_id,
6194              'INCONSISTENT XRATE INFO',
6195               p_default_last_updated_by,
6196               p_default_last_update_login,
6197               current_calling_sequence) <> TRUE) THEN
6198           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6199             AP_IMPORT_UTILITIES_PKG.Print(
6200             AP_IMPORT_INVOICES_PKG.g_debug_switch,
6201             'insert_rejections<-'||current_calling_sequence);
6202           END IF;
6203           RAISE no_xrate_base_amount_failure;
6204         END IF;
6205 
6206         l_current_invoice_status := 'N';
6207       END IF;
6208 
6209     ELSIF (p_calc_user_xrate = 'Y') AND
6210           ((p_invoice_rec.exchange_rate_type = 'User') AND
6211            (p_invoice_rec.no_xrate_base_amount IS NULL) AND
6212            (p_invoice_rec.exchange_rate is NULL)) THEN
6213 
6214       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
6215                        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
6216                         p_invoice_rec.invoice_id,
6217                         'NO EXCHANGE RATE',
6218                         p_default_last_updated_by,
6219                         p_default_last_update_login,
6220                         current_calling_sequence) <> TRUE) THEN
6221         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6222           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6223           'insert_rejections<-'||current_calling_sequence);
6224         END IF;
6225         RAISE no_xrate_base_amount_failure;
6226       END IF;
6227 
6228       l_current_invoice_status := 'N';
6229 
6230     END IF; -- Calculate user xrate is not Y and xrate base amount provided
6231   END IF; -- Multi currency flag is Y and this is a foreign currency invoice
6232 
6233   -------------------------------------------------------------------------
6234   -- Step 2 - Obtain base amount if no_xrate_base_amount null,
6235   --          invoice valid and it is a foreign currency invoice.
6236   -------------------------------------------------------------------------
6237   IF (l_current_invoice_status <> 'N' AND
6238       p_invoice_rec.no_xrate_base_amount IS NULL AND
6239       p_base_currency_code <> p_invoice_rec.invoice_currency_code) THEN
6240 
6241     debug_info := '(Check No Xrate Base Amount 2) Get invoice base amount';
6242     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6243       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6244                    debug_info);
6245     END IF;
6246 
6247     IF (p_invoice_rec.exchange_rate_type <> 'User' AND
6248     AP_UTILITIES_PKG.calculate_user_xrate (
6249                   p_invoice_rec.invoice_currency_code,
6250                   p_base_currency_code,
6251                   p_invoice_rec.exchange_date,
6252                   p_invoice_rec.exchange_rate_type) = 'N') THEN
6253       p_invoice_base_amount := gl_currency_api.convert_amount(
6254                         p_invoice_rec.invoice_currency_code,
6255                                         p_base_currency_code,
6256                                         p_invoice_rec.exchange_date,
6257                           p_invoice_rec.exchange_rate_type,
6258                     p_invoice_rec.invoice_amount);
6259     ELSE
6260       p_invoice_base_amount := ap_utilities_pkg.ap_round_currency(
6261                        (p_invoice_rec.invoice_amount *
6262                         p_invoice_rec.exchange_rate),
6263                         p_base_currency_code);
6264     END IF;
6265   END IF;
6266 
6267   p_current_invoice_status := l_current_invoice_status;
6268   RETURN (TRUE);
6269 
6270 EXCEPTION
6271   WHEN OTHERS THEN
6272     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6273       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6274                                     debug_info);
6275     END IF;
6276 
6277     IF (SQLCODE < 0) then
6278       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6279         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6280                                       SQLERRM);
6281       END IF;
6282     END IF;
6283 
6284     RETURN(FALSE);
6285 
6286 END v_check_no_xrate_base_amount;
6287 
6288 
6289 FUNCTION v_check_lines_validation (
6290          p_invoice_rec        IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
6291          p_invoice_lines_tab  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.t_lines_table,
6292          p_gl_date_from_get_info        IN            DATE,
6293          p_gl_date_from_receipt_flag    IN            VARCHAR2,
6294          p_positive_price_tolerance     IN            NUMBER,
6295          p_pa_installed                 IN            VARCHAR2,
6296          p_qty_ord_tolerance            IN            NUMBER,
6297 	 p_amt_ord_tolerance            IN            NUMBER,
6298          p_max_qty_ord_tolerance        IN            NUMBER,
6299 	 p_max_amt_ord_tolerance	IN	      NUMBER,
6300          p_min_acct_unit_inv_curr       IN            NUMBER,
6301          p_precision_inv_curr           IN            NUMBER,
6302          p_base_currency_code           IN            VARCHAR2,
6303          p_base_min_acct_unit           IN            NUMBER,
6304          p_base_precision               IN            NUMBER,
6305          p_set_of_books_id              IN            NUMBER,
6306          p_asset_book_type              IN            VARCHAR2,  -- Bug 5448579
6307          p_chart_of_accounts_id         IN            NUMBER,
6308          p_freight_code_combination_id  IN            NUMBER,
6309          p_purch_encumbrance_flag       IN            VARCHAR2,
6310 	 p_retainage_ccid		IN	      NUMBER,
6311          p_default_last_updated_by      IN            NUMBER,
6312          p_default_last_update_login    IN            NUMBER,
6313          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
6314          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
6315 
6316 
6317 
6318 IS
6319 
6320 /* For Bug - 2823140. Added trim to trailing spaces wherever necessary */
6321 /* For Bug - 6349739 Added NVL to tax classification code
6322  * Added handling for retek generated concatenated accts */
6323 
6324 CURSOR    invoice_lines IS
6325 SELECT    rowid, -- BUG 1714845
6326           invoice_line_id,
6327           line_type_lookup_code,
6328           line_number,
6329           line_group_number,
6330           amount,
6331           NULL, -- base amount
6332           accounting_date,
6333           NULL, --period name
6334           deferred_acctg_flag,
6335           def_acctg_start_date,
6336           def_acctg_end_date,
6337           def_acctg_number_of_periods,
6338           def_acctg_period_type,
6339           trim(description),
6340           prorate_across_flag,
6341           NULL, -- match_type
6342           po_header_id,
6343           po_number,
6344           po_line_id,
6345           po_line_number,
6346           po_release_id,
6347           release_num,
6348           po_line_location_id,
6349           po_shipment_num,
6350           po_distribution_id,
6351           po_distribution_num,
6352           unit_of_meas_lookup_code,
6353           inventory_item_id,
6354           item_description,
6355           quantity_invoiced,
6356           ship_to_location_code,
6357           unit_price,
6358           final_match_flag,
6359           distribution_set_id,
6360           distribution_set_name,
6361           NULL, -- partial segments
6362           -- bug 6349739
6363           DECODE(AP_IMPORT_INVOICES_PKG.g_source,
6364           'RETEK',
6365           TRANSLATE(RTRIM(dist_code_concatenated,'-'),
6366                     '-',
6367                     AP_IMPORT_INVOICES_PKG.g_segment_delimiter),
6368           dist_code_concatenated), -- 6349739
6369           dist_code_combination_id,
6370           awt_group_id,
6371           awt_group_name,
6372           pay_awt_group_id,--bug6639866
6373           pay_awt_group_name,--bug6639866
6374           balancing_segment,
6375           cost_center_segment,
6376           account_segment,
6377           trim(attribute_category),
6378           trim(attribute1),
6379           trim(attribute2),
6380           trim(attribute3),
6381           trim(attribute4),
6382           trim(attribute5),
6383           trim(attribute6),
6384           trim(attribute7),
6385           trim(attribute8),
6386           trim(attribute9),
6387           trim(attribute10),
6388           trim(attribute11),
6389           trim(attribute12),
6390           trim(attribute13),
6391           trim(attribute14),
6392           trim(attribute15),
6393           trim(global_attribute_category),
6394           trim(global_attribute1),
6395           trim(global_attribute2),
6396           trim(global_attribute3),
6397           trim(global_attribute4),
6398           trim(global_attribute5),
6399           trim(global_attribute6),
6400           trim(global_attribute7),
6401           trim(global_attribute8),
6402           trim(global_attribute9),
6403           trim(global_attribute10),
6404           trim(global_attribute11),
6405           trim(global_attribute12),
6406           trim(global_attribute13),
6407           trim(global_attribute14),
6408           trim(global_attribute15),
6409           trim(global_attribute16),
6410           trim(global_attribute17),
6411           trim(global_attribute18),
6412           trim(global_attribute19),
6413           trim(global_attribute20),
6414           project_id,
6415           task_id,
6416           award_id,
6417           expenditure_type,
6418           expenditure_item_date,
6419           expenditure_organization_id,
6420           pa_addition_flag,
6421           pa_quantity,
6422           stat_amount,
6423           type_1099,
6424           income_tax_region,
6425           assets_tracking_flag,
6426           asset_book_type_code,
6427           asset_category_id,
6428           serial_number,
6429           manufacturer,
6430           model_number,
6431           warranty_number,
6432           price_correction_flag,
6433           price_correct_inv_num,
6434           NULL, -- corrected_inv_id.
6435                 -- This will populated based on the price_correct_inv_num
6436           price_correct_inv_line_num,
6437           receipt_number,
6438           receipt_line_number,
6439           rcv_transaction_id,
6440 	  NULL,               -- bug 7344899
6441           match_option,
6442           packing_slip,
6443           vendor_item_num,
6444           taxable_flag,
6445           pa_cc_ar_invoice_id,
6446           pa_cc_ar_invoice_line_num,
6447           pa_cc_processed_code,
6448           reference_1,
6449           reference_2,
6450           credit_card_trx_id,
6451           requester_id,
6452           org_id,
6453           NULL, -- program_application_id
6454           NULL, -- program_id
6455           NULL, -- request_id
6456           NULL,  -- program_update_date
6457           control_amount,
6458           assessable_value,
6459           default_dist_ccid,
6460           primary_intended_use,
6461           ship_to_location_id,
6462           product_type,
6463           product_category,
6464           product_fisc_classification,
6465           user_defined_fisc_class,
6466           trx_business_category,
6467           tax_regime_code,
6468           tax,
6469           tax_jurisdiction_code,
6470           tax_status_code,
6471           tax_rate_id,
6472           tax_rate_code,
6473           tax_rate,
6474           incl_in_taxable_line_flag,
6475 	  application_id,
6476 	  product_table,
6477 	  reference_key1,
6478 	  reference_key2,
6479 	  reference_key3,
6480 	  reference_key4,
6481 	  reference_key5,
6482 	  purchasing_category_id,
6483 	  purchasing_category,
6484 	  cost_factor_id,
6485 	  cost_factor_name,
6486 	  source_application_id,
6487 	  source_entity_code,
6488 	  source_event_class_code,
6489 	  source_trx_id,
6490 	  source_line_id,
6491 	  source_trx_level_type,
6492 	  nvl(tax_classification_code, tax_code), --bug 6349739
6493 	  NULL, -- retained_amount
6494 	  amount_includes_tax_flag,
6495 	  --Bug6167068 starts Added the following columns to get related data for Expense reports
6496 	  cc_reversal_flag,
6497 	  company_prepaid_invoice_id,
6498 	  expense_group,
6499 	  justification,
6500 	  merchant_document_number,
6501 	  merchant_name,
6502 	  merchant_reference,
6503 	  merchant_taxpayer_id,
6504 	  merchant_tax_reg_number,
6505 	  receipt_conversion_rate,
6506 	  receipt_currency_amount,
6507 	  receipt_currency_code,
6508 	  country_of_supply
6509 	  --Bug6167068 ends
6510      FROM ap_invoice_lines_interface
6511     WHERE invoice_id = p_invoice_rec.invoice_id
6512  ORDER BY invoice_line_id;
6513 --   FOR UPDATE OF invoice_line_id; -- Bug 1714845
6514 
6515 /* Bug 6369356:
6516  * For Retek invoices having multiple tax lines with same tax code,
6517  * we need to summarize the tax amounts on tax classification code.*/
6518 
6519 CURSOR    invoice_lines_tax_summarized IS
6520 SELECT    rowid, -- BUG 1714845
6521           invoice_line_id,
6522           line_type_lookup_code,
6523           line_number,
6524           line_group_number,
6525           --amount,
6526           -- Bug 6369356 summarize tax lines
6527           DECODE(line_type_lookup_code , 'TAX',
6528                  (SELECT SUM(ail3.amount)
6529                   FROM   ap_invoice_lines_interface ail3
6530                   WHERE  ail3.tax_code = ail.tax_code
6531                   AND    ail3.line_type_lookup_code = 'TAX'
6532                   AND    ail3.invoice_id = ail.invoice_id
6533                   GROUP BY tax_code),
6534                   amount) amount,
6535           -- Bug 6369356
6536           NULL, -- base amount
6537           accounting_date,
6538           NULL, --period name
6539           deferred_acctg_flag,
6540           def_acctg_start_date,
6541           def_acctg_end_date,
6542           def_acctg_number_of_periods,
6543           def_acctg_period_type,
6544           trim(description),
6545           prorate_across_flag,
6546           NULL, -- match_type
6547           po_header_id,
6548           po_number,
6549           po_line_id,
6550           po_line_number,
6551           po_release_id,
6552           release_num,
6553           po_line_location_id,
6554           po_shipment_num,
6555           po_distribution_id,
6556           po_distribution_num,
6557           unit_of_meas_lookup_code,
6558           inventory_item_id,
6559           item_description,
6560           quantity_invoiced,
6561           ship_to_location_code,
6562           unit_price,
6563           final_match_flag,
6564           distribution_set_id,
6565           distribution_set_name,
6566           NULL, -- partial segments
6567           -- bug 6349739
6568           DECODE(AP_IMPORT_INVOICES_PKG.g_source,
6569           'RETEK',
6570           TRANSLATE(RTRIM(dist_code_concatenated,'-'),
6571                     '-',
6572                     AP_IMPORT_INVOICES_PKG.g_segment_delimiter),
6573           dist_code_concatenated), -- 6349739
6574           dist_code_combination_id,
6575           awt_group_id,
6576           awt_group_name,
6577           pay_awt_group_id,--bug6639866
6578           pay_awt_group_name,--bug6639866
6579           balancing_segment,
6580           cost_center_segment,
6581           account_segment,
6582           trim(attribute_category),
6583           trim(attribute1),
6584           trim(attribute2),
6585           trim(attribute3),
6586           trim(attribute4),
6587           trim(attribute5),
6588           trim(attribute6),
6589           trim(attribute7),
6590           trim(attribute8),
6591           trim(attribute9),
6592           trim(attribute10),
6593           trim(attribute11),
6594           trim(attribute12),
6595           trim(attribute13),
6596           trim(attribute14),
6597           trim(attribute15),
6598           trim(global_attribute_category),
6599           trim(global_attribute1),
6600           trim(global_attribute2),
6601           trim(global_attribute3),
6602           trim(global_attribute4),
6603           trim(global_attribute5),
6604           trim(global_attribute6),
6605           trim(global_attribute7),
6606           trim(global_attribute8),
6607           trim(global_attribute9),
6608           trim(global_attribute10),
6609           trim(global_attribute11),
6610           trim(global_attribute12),
6611           trim(global_attribute13),
6612           trim(global_attribute14),
6613           trim(global_attribute15),
6614           trim(global_attribute16),
6615           trim(global_attribute17),
6616           trim(global_attribute18),
6617           trim(global_attribute19),
6618           trim(global_attribute20),
6619           project_id,
6620           task_id,
6621           award_id,
6622           expenditure_type,
6623           expenditure_item_date,
6624           expenditure_organization_id,
6625           pa_addition_flag,
6626           pa_quantity,
6627           stat_amount,
6628           type_1099,
6629           income_tax_region,
6630           assets_tracking_flag,
6631           asset_book_type_code,
6632           asset_category_id,
6633           serial_number,
6634           manufacturer,
6635           model_number,
6636           warranty_number,
6637           price_correction_flag,
6638           price_correct_inv_num,
6639           NULL, -- corrected_inv_id.
6640                 -- This will populated based on the price_correct_inv_num
6641           price_correct_inv_line_num,
6642           receipt_number,
6643           receipt_line_number,
6644           rcv_transaction_id,
6645 	  NULL,               -- bug 7344899
6646           match_option,
6647           packing_slip,
6648           vendor_item_num,
6649           taxable_flag,
6650           pa_cc_ar_invoice_id,
6651           pa_cc_ar_invoice_line_num,
6652           pa_cc_processed_code,
6653           reference_1,
6654           reference_2,
6655           credit_card_trx_id,
6656           requester_id,
6657           org_id,
6658           NULL, -- program_application_id
6659           NULL, -- program_id
6660           NULL, -- request_id
6661           NULL,  -- program_update_date
6662           control_amount,
6663           assessable_value,
6664           default_dist_ccid,
6665           primary_intended_use,
6666           ship_to_location_id,
6667           product_type,
6668           product_category,
6669           product_fisc_classification,
6670           user_defined_fisc_class,
6671           trx_business_category,
6672           tax_regime_code,
6673           tax,
6674           tax_jurisdiction_code,
6675           tax_status_code,
6676           tax_rate_id,
6677           tax_rate_code,
6678           tax_rate,
6679           incl_in_taxable_line_flag,
6680           application_id,
6681           product_table,
6682           reference_key1,
6683           reference_key2,
6684           reference_key3,
6685           reference_key4,
6686           reference_key5,
6687           purchasing_category_id,
6688           purchasing_category,
6689           cost_factor_id,
6690           cost_factor_name,
6691           source_application_id,
6692           source_entity_code,
6693           source_event_class_code,
6694           source_trx_id,
6695           source_line_id,
6696           source_trx_level_type,
6697           NVL(tax_classification_code, tax_code), --bug 6349739
6698           NULL, -- retained_amount
6699           amount_includes_tax_flag,
6700           --Bug6167068 starts Added the following columns to get related data
6701           --           for Expense reports
6702           cc_reversal_flag,
6703           company_prepaid_invoice_id,
6704           expense_group,
6705           justification,
6706           merchant_document_number,
6707           merchant_name,
6708           merchant_reference,
6709           merchant_taxpayer_id,
6710           merchant_tax_reg_number,
6711           receipt_conversion_rate,
6712           receipt_currency_amount,
6713           receipt_currency_code,
6714           country_of_supply
6715           --Bug6167068 ends
6716      FROM ap_invoice_lines_interface ail
6717     WHERE invoice_id = p_invoice_rec.invoice_id
6718     -- Bug 6369356
6719     AND   ((line_type_lookup_code <> 'TAX')
6720           OR ( line_type_lookup_code = 'TAX' AND
6721           rowid =(SELECT max(ail2.rowid)
6722                   FROM   ap_invoice_lines_interface ail2
6723                   WHERE  ail2.tax_code = ail.tax_code
6724                   AND    ail2.line_type_lookup_code = 'TAX'
6725                   AND    ail2.invoice_id = ail.invoice_id
6726                   GROUP BY tax_code)
6727                   )
6728                   )
6729     -- Bug 6369356
6730  ORDER BY invoice_line_id;
6731 --   FOR UPDATE OF invoice_line_id; -- Bug 1714845
6732 
6733 check_lines_failure          EXCEPTION;
6734 l_current_invoice_status      VARCHAR2(1) := 'Y';
6735 l_temp_line_status          VARCHAR2(1) := 'Y';
6736 l_max_line_number             NUMBER;
6737 l_employee_id                  NUMBER;
6738 l_error_message              VARCHAR2(200);
6739 l_pa_built_account            NUMBER := 0;
6740 current_calling_sequence      VARCHAR2(2000);
6741 debug_info                 VARCHAR2(500);
6742 /* bug 5039042 */
6743 l_product_registered       VARCHAR2(1) := 'N';
6744 l_dummy                    VARCHAR2(100);
6745 
6746 
6747 BEGIN
6748   -- Update the calling sequence
6749   --
6750   current_calling_sequence :=
6751     'AP_IMPORT_VALIDATION_PKG.v_check_lines_validation<-'||P_calling_sequence;
6752 
6753   --------------------------------------------------------
6754   -- Step 1
6755   -- Get Employee ID for PA Related Invoice Line
6756   ---------------------------------------------------------
6757 
6758   --Payment Requests: Added IF condition for Payment Requests
6759   IF (p_invoice_rec.invoice_type_lookup_code <> 'PAYMENT REQUEST') THEN
6760 
6761      debug_info := '(Check_lines 1) Call Get_employee_id';
6762      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6763        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6764                                      debug_info);
6765      END IF;
6766 
6767      IF (AP_IMPORT_UTILITIES_PKG.get_employee_id(
6768            p_invoice_rec.invoice_id,
6769            p_invoice_rec.vendor_id,
6770            l_employee_id,                -- OUT
6771            p_default_last_updated_by,
6772            p_default_last_update_login,
6773            l_temp_line_status,           -- OUT
6774            p_calling_sequence    => current_calling_sequence) <> TRUE ) THEN
6775        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6776          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6777                          'get_employee_id<-' ||current_calling_sequence);
6778        END IF;
6779        RAISE check_lines_failure;
6780      END IF;
6781   END IF;
6782 
6783   --
6784   -- show output values (only if debug_switch = 'Y')
6785   --
6786   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6787     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6788     '------------------> l_temp_line_status = '||l_temp_line_status
6789     ||' l_employee_id = '||to_char(l_employee_id));
6790   END IF;
6791 
6792   -- Since vendor is already validated
6793   -- Rejection should happen only if the Project Related
6794   -- invoices do not have a valid employee_id in PO_vendors
6795 
6796   IF (l_temp_line_status = 'N') THEN
6797      l_current_invoice_status := l_temp_line_status;
6798   END IF;
6799 
6800   --------------------------------------------------------------------------
6801   -- Step 2
6802   -- Get max line number for the invoice to be used in case a line does not
6803   -- provide a line number
6804   --------------------------------------------------------------------------
6805   debug_info := '(Check Lines 2) Get Max Line Number';
6806   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
6807     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6808                                   debug_info);
6809   END IF;
6810   --
6811   IF AP_IMPORT_INVOICES_PKG.g_source = 'RETEK' THEN
6812       BEGIN
6813           SELECT NVL(MAX(line_number),0)
6814           INTO l_max_line_number
6815           FROM ap_invoice_lines_interface ail
6816          WHERE invoice_id = p_invoice_rec.invoice_id
6817          AND   ((line_type_lookup_code <> 'TAX')
6818           OR ( line_type_lookup_code = 'TAX' AND
6819           rowid =(SELECT MAX(ail2.rowid)
6820                   FROM   ap_invoice_lines_interface ail2
6821                   WHERE  ail2.tax_code = ail.tax_code
6822                   AND    ail2.line_type_lookup_code = 'TAX'
6823                   AND    ail2.invoice_id = ail.invoice_id
6824                   GROUP BY tax_code)
6825                   )
6826                   );
6827       EXCEPTION
6828         WHEN OTHERS THEN
6829           RAISE check_lines_failure;
6830       END;
6831   -- Bug 6369356
6832   --
6833   ELSIF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
6834       BEGIN
6835 	--bugfix:4745899 , added the NVL condition
6836         SELECT NVL(MAX(line_number),0)
6837           INTO l_max_line_number
6838           FROM ap_invoice_lines_interface
6839          WHERE invoice_id = p_invoice_rec.invoice_id;
6840 
6841       EXCEPTION
6842         WHEN OTHERS THEN
6843           RAISE check_lines_failure;
6844       END;
6845   ELSE
6846     --
6847     l_max_line_number :=   p_invoice_lines_tab.COUNT;
6848     --
6849   END IF;
6850   --------------------------------------------------------------------------
6851   -- Step 3
6852   -- Open invoice_lines cursor.
6853   -- Retropricing: For PPA's the p_invoice_lines_tab is populated from
6854   -- AP_PPA_LINES_GT
6855   --------------------------------------------------------------------------
6856   debug_info := '(Check Lines 3) Open Cursor: invoice_lines';
6857   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6858     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6859                                   debug_info);
6860   END IF;
6861 
6862   -- Bug 6369356
6863   IF AP_IMPORT_INVOICES_PKG.g_source = 'RETEK' THEN
6864       OPEN invoice_lines_tax_summarized;
6865       FETCH invoice_lines_tax_summarized BULK COLLECT INTO p_invoice_lines_tab;
6866       CLOSE invoice_lines_tax_summarized;
6867   ELSIF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
6868       OPEN invoice_lines;
6869       FETCH invoice_lines BULK COLLECT INTO p_invoice_lines_tab;
6870       CLOSE invoice_lines;
6871   END IF;
6872 
6873   FOR i IN 1..p_invoice_lines_tab.COUNT  --Retropricing
6874   LOOP
6875     --------------------------------------------------------------------------
6876     -- Step 4
6877     -- Loop through fetched invoice lines
6878     --------------------------------------------------------------------------
6879     debug_info := '(Check Lines 4) Looping through fetched invoice lines';
6880     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6881       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
6882                                     debug_info);
6883     END IF;
6884 
6885     -- Retropricing: Base Amount is populated for proposed PPA Lines
6886     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
6887         p_invoice_lines_tab(i).base_amount :=
6888              ap_utilities_pkg.ap_round_currency(
6889                 p_invoice_lines_tab(i).amount*p_invoice_rec.exchange_rate,
6890                 p_base_currency_code );
6891     END IF;
6892 
6893     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
6894       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch ,
6895       '------------------>  invoice_line_id = '
6896         ||to_char(p_invoice_lines_tab(i).invoice_line_id )
6897       ||' line_type_lookup_code = '
6898         || p_invoice_lines_tab(i).line_type_lookup_code
6899       || 'line_number = '    || to_char(p_invoice_lines_tab(i).line_number)
6900       || 'line_group_number = '
6901         || to_char(p_invoice_lines_tab(i).line_group_number)
6902       || 'amount = '            || to_char(p_invoice_lines_tab(i).amount)
6903       || 'base amount  '
6904         || to_char(p_invoice_lines_tab(i).base_amount)
6905       || 'accounting_date = '
6906         || to_char(p_invoice_lines_tab(i).accounting_date)
6907       || 'deferred_acctg_flag = '|| p_invoice_lines_tab(i).deferred_acctg_flag
6908       || 'def_acctg_start_date = '
6909         || to_char(p_invoice_lines_tab(i).def_acctg_start_date)
6910       || 'def_acctg_end_date = '
6911         || to_char(p_invoice_lines_tab(i).def_acctg_end_date)
6912       || 'def_acctg_number_of_period = '
6913         || to_char(p_invoice_lines_tab(i).def_acctg_number_of_periods)
6914       || 'def_acctg_period_type = '
6915         || p_invoice_lines_tab(i).def_acctg_period_type
6916       || 'description = '    || p_invoice_lines_tab(i).description
6917       || 'prorate_across_flag = '
6918         || p_invoice_lines_tab(i).prorate_across_flag
6919       || 'po_header_id = ' ||    to_char(p_invoice_lines_tab(i).po_header_id)
6920       || 'po_number = '    || to_char(p_invoice_lines_tab(i).po_number)
6921       || 'po_line_id = '    || to_char(p_invoice_lines_tab(i).po_line_id)
6922       || 'po_line_number = ' || to_char(p_invoice_lines_tab(i).po_line_number)
6923       || 'po_release_id = '    || to_char(p_invoice_lines_tab(i).po_release_id)
6924       || 'release_num = '    || to_char(p_invoice_lines_tab(i).release_num)
6925       || 'po_line_location_id = '
6926         || to_char(p_invoice_lines_tab(i).po_line_location_id)
6927       || 'po_shipment_num = '
6928         || to_char(p_invoice_lines_tab(i).po_shipment_num)
6929       || 'po_distribution_id = '
6930         || to_char(p_invoice_lines_tab(i).po_distribution_id)
6931       || 'po_distribution_num = '
6932         || to_char(p_invoice_lines_tab(i).po_distribution_num)
6933       || 'unit_of_meas_lookup_code = '
6934         || p_invoice_lines_tab(i).unit_of_meas_lookup_code
6935       || 'inventory_item_id = '
6936         || to_char(p_invoice_lines_tab(i).inventory_item_id)
6937       || 'item_description = '    || p_invoice_lines_tab(i).item_description
6938       || 'purchasing_category_id = '   || p_invoice_lines_tab(i).purchasing_category_id
6939       || 'purchasing_category = '  || p_invoice_lines_tab(i).purchasing_category
6940       || 'quantity_invoiced = '
6941         || to_char(p_invoice_lines_tab(i).quantity_invoiced)
6942       || 'ship_to_location_code = '
6943         || p_invoice_lines_tab(i).ship_to_location_code
6944       || 'unit_price = '
6945         || to_char(p_invoice_lines_tab(i).unit_price)
6946       || 'final_match_flag = '    || p_invoice_lines_tab(i).final_match_flag
6947       || 'distribution_set_id = '
6948         || to_char(p_invoice_lines_tab(i).distribution_set_id)
6949       || 'distribution_set_name = '
6950      || p_invoice_lines_tab(i).distribution_set_name
6951       || 'dist_code_concatenated = '
6952         || p_invoice_lines_tab(i).dist_code_concatenated
6953       || 'dist_code_combination_id = '
6954         || to_char(p_invoice_lines_tab(i).dist_code_combination_id)
6955       || 'awt_group_id = '
6956         || to_char(p_invoice_lines_tab(i).awt_group_id)
6957       || 'awt_group_name = '    || p_invoice_lines_tab(i).awt_group_name
6958       || 'balancing_segment = '    || p_invoice_lines_tab(i).balancing_segment
6959       || 'cost_center_segment = ' || p_invoice_lines_tab(i).cost_center_segment
6960       || 'account_segment = '      || p_invoice_lines_tab(i).account_segment
6961       || 'attribute_category = '  || p_invoice_lines_tab(i).attribute_category
6962       || 'attribute1 = '    || p_invoice_lines_tab(i).attribute1
6963       || 'attribute2 = '    || p_invoice_lines_tab(i).attribute2
6964       || 'attribute3 = '    || p_invoice_lines_tab(i).attribute3
6965       || 'attribute4 = '    || p_invoice_lines_tab(i).attribute4
6966       || 'attribute5 = '    || p_invoice_lines_tab(i).attribute5
6967       || 'attribute6 = '    || p_invoice_lines_tab(i).attribute6
6968       || 'attribute7 = '    || p_invoice_lines_tab(i).attribute7
6969       || 'attribute8 = '    || p_invoice_lines_tab(i).attribute8
6970       || 'attribute9 = '    || p_invoice_lines_tab(i).attribute9
6971       || 'attribute10 = '    || p_invoice_lines_tab(i).attribute10
6972       || 'attribute11 = '    || p_invoice_lines_tab(i).attribute11
6973       || 'attribute12 = '    || p_invoice_lines_tab(i).attribute12
6974       || 'attribute13 = '    || p_invoice_lines_tab(i).attribute13
6975       || 'attribute14 = '    || p_invoice_lines_tab(i).attribute14
6976       || 'attribute15 = '    || p_invoice_lines_tab(i).attribute15
6977       || 'global_attribute_category = '
6978         || p_invoice_lines_tab(i).global_attribute_category
6979       || 'global_attribute1 = '    || p_invoice_lines_tab(i).global_attribute1
6980       || 'global_attribute2 = '    || p_invoice_lines_tab(i).global_attribute2
6981       || 'global_attribute3 = '    || p_invoice_lines_tab(i).global_attribute3
6982       || 'global_attribute4 = '    || p_invoice_lines_tab(i).global_attribute4
6983       || 'global_attribute5 = '    || p_invoice_lines_tab(i).global_attribute5
6984       || 'global_attribute6 = '    || p_invoice_lines_tab(i).global_attribute6
6985       || 'global_attribute7 = '    || p_invoice_lines_tab(i).global_attribute7
6986       || 'global_attribute8 = '    || p_invoice_lines_tab(i).global_attribute8
6987       || 'global_attribute9 = '    || p_invoice_lines_tab(i).global_attribute9
6988       || 'global_attribute10 = '|| p_invoice_lines_tab(i).global_attribute10
6989       || 'global_attribute11 = '|| p_invoice_lines_tab(i).global_attribute11
6990       || 'global_attribute12 = '|| p_invoice_lines_tab(i).global_attribute12
6991       || 'global_attribute13 = '|| p_invoice_lines_tab(i).global_attribute13
6992       || 'global_attribute14 = '|| p_invoice_lines_tab(i).global_attribute14
6993       || 'global_attribute15 = '|| p_invoice_lines_tab(i).global_attribute15
6994       || 'global_attribute16 = '|| p_invoice_lines_tab(i).global_attribute16
6995       || 'global_attribute17 = '|| p_invoice_lines_tab(i).global_attribute17
6996       || 'global_attribute18 = '|| p_invoice_lines_tab(i).global_attribute18
6997       || 'global_attribute19 = '|| p_invoice_lines_tab(i).global_attribute19
6998       || 'global_attribute20 = '|| p_invoice_lines_tab(i).global_attribute20
6999       || 'project_id = '         || to_char(p_invoice_lines_tab(i).project_id)
7000       || 'task_id = '           || to_char(p_invoice_lines_tab(i).task_id)
7001       || 'award_id = '            || to_char(p_invoice_lines_tab(i).award_id)
7002       || 'expenditure_type = '    || p_invoice_lines_tab(i).expenditure_type
7003       || 'expenditure_item_date = '
7004         || to_char(p_invoice_lines_tab(i).expenditure_item_date)
7005       || 'expenditure_organization_id = '
7006         || p_invoice_lines_tab(i).expenditure_organization_id
7007       || 'pa_addition_flag = '    || p_invoice_lines_tab(i).pa_addition_flag
7008       || 'pa_quantity = '    || to_char(p_invoice_lines_tab(i).pa_quantity)
7009       || 'stat_amount = '    || to_char(p_invoice_lines_tab(i).stat_amount)
7010       || 'type_1099 = '    || p_invoice_lines_tab(i).type_1099
7011       || 'income_tax_region = '    || p_invoice_lines_tab(i).income_tax_region
7012       || 'asset_tracking_flag = '
7013         || p_invoice_lines_tab(i).assets_tracking_flag
7014       || 'asset_book_type_code = '
7015         || p_invoice_lines_tab(i).asset_book_type_code
7016       || 'asset_category_id = '
7017         || to_char(p_invoice_lines_tab(i).asset_category_id)
7018       || 'serial_number = '    || to_char(p_invoice_lines_tab(i).serial_number)
7019       || 'manufacturer = '    || p_invoice_lines_tab(i).manufacturer
7020       || 'model_number = '    || p_invoice_lines_tab(i).model_number
7021       || 'warranty_number = '    || p_invoice_lines_tab(i).warranty_number
7022       || 'price_correction_flag = '
7023         || p_invoice_lines_tab(i).price_correction_flag
7024       || 'price_correct_inv_num = '
7025         || p_invoice_lines_tab(i).price_correct_inv_num
7026       || 'price_correct_inv_id = '
7027         || p_invoice_lines_tab(i).corrected_inv_id
7028       || 'price_correct_inv_line_num = '
7029         || p_invoice_lines_tab(i).price_correct_inv_line_num
7030       || 'receipt_number = '    || p_invoice_lines_tab(i).receipt_number
7031       || 'receipt_line_number = '
7032         || p_invoice_lines_tab(i).receipt_line_number
7033       || 'rcv_transaction_id = '
7034         || to_char(p_invoice_lines_tab(i).rcv_transaction_id)
7035       || 'match_option = '    || p_invoice_lines_tab(i).match_option
7036       || 'packing_slip = '    || p_invoice_lines_tab(i).packing_slip
7037       || 'vendor_item_num = '    || p_invoice_lines_tab(i).vendor_item_num
7038       || 'pa_cc_ar_invoice_id = '
7039         || to_char(p_invoice_lines_tab(i).pa_cc_ar_invoice_id)
7040       || 'pa_cc_ar_invoice_line_num = '
7041         ||to_char(p_invoice_lines_tab(i).pa_cc_ar_invoice_line_num)
7042       ||'pa_cc_processed_code = ' || p_invoice_lines_tab(i).pa_cc_processed_code
7043       || 'reference_1 = '    || p_invoice_lines_tab(i).reference_1
7044       || 'reference_2 = '    || p_invoice_lines_tab(i).reference_2
7045       || 'credit_card_trx_id = '
7046         || to_char(p_invoice_lines_tab(i).credit_card_trx_id)
7047       || 'requester_id = '    || to_char(p_invoice_lines_tab(i).requester_id)
7048       || 'org_id = '    || to_char(p_invoice_lines_tab(i).org_id)
7049     );
7050     END IF;
7051 
7052     -------------------------------------------------------------------------
7053     -- Step 5
7054     -- Validate line's org_id.
7055     -- Retropricing: Org Id's are populated for PPA Lines
7056     -------------------------------------------------------------------------
7057     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN   --Retropricing
7058         debug_info := '(Check Lines 5) Validate org id for line';
7059         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7060           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7061                                         debug_info);
7062         END IF;
7063 
7064         IF p_invoice_lines_tab(i).org_id IS NOT NULL THEN
7065           debug_info := '(Check_lines 5.0) Org Id Is Not Null';
7066           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7067             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7068                                           debug_info);
7069           END IF;
7070 
7071           IF p_invoice_lines_tab(i).org_id <> p_invoice_rec.org_id THEN
7072 
7073             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
7074                                 (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
7075                                   p_invoice_rec.invoice_id,
7076                                   'INCONSISTENT OPERATING UNITS',
7077                                   p_default_last_updated_by,
7078                                   p_default_last_update_login,
7079                                   current_calling_sequence) <> TRUE ) Then
7080               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7081                 AP_IMPORT_UTILITIES_PKG.Print(
7082                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
7083                 'insert_rejections<- '      ||current_calling_sequence);
7084               END IF;
7085               RAISE check_lines_failure;
7086             END IF;
7087 
7088             l_current_invoice_status := 'N';
7089             EXIT;
7090           END IF;
7091 
7092         ELSE
7093 
7094           UPDATE ap_invoice_lines_interface
7095              SET org_id = p_invoice_rec.org_id
7096            WHERE rowid = p_invoice_lines_tab(i).row_id;
7097 
7098           p_invoice_lines_tab(i).org_id := p_invoice_rec.org_id;
7099         END IF;
7100     END IF;   -- source <> PPA
7101     --------------------------------------------------------------------
7102     -- Step 6
7103     -- Get new invoice line id.
7104     -- Retropricing: The code below will not execute for PPA's.
7105     -- Invoice_line_id is present for PPA's
7106     --------------------------------------------------------------------
7107     IF (p_invoice_lines_tab(i).invoice_line_id is NULL) THEN
7108         --
7109       debug_info := '(Check_lines 6.1) Get new invoice_line_id';
7110       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7111         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7112                                       debug_info);
7113       END IF;
7114 
7115       debug_info := '(Check_lines 6.2) Update new invoice_line_id to '
7116                     ||'ap_invoice_lines_interface';
7117       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7118         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7119                                       debug_info);
7120       END IF;
7121 
7122       UPDATE ap_invoice_lines_interface
7123          SET invoice_line_id =  ap_invoice_lines_interface_s.NEXTVAL
7124        WHERE rowid = p_invoice_lines_tab(i).row_id
7125       RETURNING invoice_line_id INTO p_invoice_lines_tab(i).invoice_line_id;
7126     END IF;
7127 
7128     ------------------------------------------------------------------------
7129     -- Step 7
7130     -- Check for partial segments
7131     -- Retropricing: The code below will not execute for PPA's.
7132     ------------------------------------------------------------------------
7133     IF (p_invoice_lines_tab(i).dist_code_concatenated IS NOT NULL) THEN
7134       debug_info := '(v_check_lines 7.0) Check for partial Segments';
7135       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7136         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7137                                       debug_info);
7138       END IF;
7139 
7140       IF (AP_UTILITIES_PKG.Check_partial(
7141             p_invoice_lines_tab(i).dist_code_concatenated,  -- IN
7142              P_invoice_lines_tab(i).partial_segments,        -- OUT
7143             p_set_of_books_id,                              -- IN
7144             l_error_message,                                 -- OUT
7145             current_calling_sequence) <> TRUE) THEN
7146         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7147           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7148           'AP_UTILITIES_PKG.Check_Partial<-'||current_calling_sequence);
7149         END IF;
7150         RAISE check_lines_failure;
7151       END IF;
7152 
7153       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7154           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7155             '------------------> partial_segments = '
7156             || p_invoice_lines_tab(i).partial_segments
7157             ||'l_error_message = '||l_error_message
7158             ||'dist_code_concatenated = '
7159             || p_invoice_lines_tab(i).dist_code_concatenated);
7160       END IF;
7161     END IF; --dist_code_concatenated
7162 
7163     -------------------------------------------------
7164     -- step 8
7165     -- checking for the precision of the lines amount
7166     -------------------------------------------------
7167     IF (p_invoice_lines_tab(i).amount <> 0 AND
7168         p_invoice_lines_tab(i).invoice_line_id is not null)  THEN
7169 
7170       debug_info := '(Check Invoice Line amount 8) Check for invoice line '
7171                     ||'amount if it is not exceeding precision';
7172       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7173         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7174                                       debug_info);
7175       END IF;
7176       IF (AP_IMPORT_VALIDATION_PKG.v_check_invoice_line_amount (
7177                 p_invoice_lines_tab(i),
7178                 p_precision_inv_curr,
7179                 p_default_last_updated_by,
7180                 p_default_last_update_login,
7181                 p_current_invoice_status => l_temp_line_status,  --IN OUT
7182                 p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
7183         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7184           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7185           'v_check_line_amount<-'||current_calling_sequence);
7186         END IF;
7187         RAISE check_lines_failure;
7188 
7189       END IF;
7190 
7191       IF (l_temp_line_status = 'N') THEN
7192         l_current_invoice_status := l_temp_line_status;
7193       END IF;
7194       --
7195       -- show output values (only if debug_switch = 'Y')
7196       --
7197       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7198         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7199           '------------------>
7200           l_temp_invoice_status  = '||l_temp_line_status);
7201       END IF;
7202     END IF;
7203 
7204     --------------------------------------------------------
7205     -- Step 9
7206     -- check for PO Information
7207     -- only for ITEM Lines
7208     ---------------------------------------------------------
7209     debug_info := '(Check_lines 9) Call v_check_po_info only for ITEM Lines';
7210     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7211       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7212                                     debug_info);
7213     END IF;
7214 
7215     IF (nvl(p_invoice_lines_tab(i).line_type_lookup_code, 'ITEM' )
7216          IN ('ITEM','RETROITEM')) THEN
7217       debug_info := '(Check_lines 9.1) This is an ITEM Line';
7218       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7219         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7220                                       debug_info);
7221       END IF;
7222 
7223       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_po_info(
7224            p_invoice_rec,                        -- IN
7225            p_invoice_lines_tab(i),                -- IN OUT
7226            p_set_of_books_id,                      -- IN
7227            p_positive_price_tolerance,             -- IN
7228            p_qty_ord_tolerance,                    -- IN
7229 	   p_amt_ord_tolerance,			   -- IN
7230            p_max_qty_ord_tolerance,                -- IN
7231 	   p_max_amt_ord_tolerance,		   -- IN
7232            p_default_last_updated_by,              -- IN
7233            p_default_last_update_login,            -- IN
7234            p_current_invoice_status => l_temp_line_status,  -- IN OUT NOCOPY
7235            p_calling_sequence       => current_calling_sequence)
7236           <> TRUE )THEN
7237         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7238           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7239             'v_check_po_info<-' ||current_calling_sequence);
7240         END IF;
7241         RAISE check_lines_failure;
7242       END IF;
7243 
7244       --
7245       -- show output values (only if debug_switch = 'Y')
7246       --
7247       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7248         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7249           '------------------> l_temp_line_status = '|| l_temp_line_status);
7250       END IF;
7251 
7252       -- We need to set the current status to 'N' only if the temp line status
7253       -- returns 'N'. So all temp returns of 'N' will overwrite the current
7254       -- invoice status to 'N' which finally would be returned to the calling
7255       -- function.
7256       IF (l_temp_line_status = 'N') THEN
7257         l_current_invoice_status := l_temp_line_status;
7258       END IF;
7259 
7260     END IF; -- for ITEM line type lookup
7261 
7262     --------------------------------------------------------
7263     -- Step 10
7264     -- Check for receipt information if match option = 'R'
7265     --------------------------------------------------------
7266     debug_info := '(Check_lines 10) Call v_check_receipt_info';
7267     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7268       AP_IMPORT_UTILITIES_PKG.Print(
7269         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
7270     END IF;
7271 
7272 --Bug 5225547 added the below condition to call v_check_receipt_info
7273 
7274   IF (p_invoice_lines_tab(i).match_option = 'R') Then
7275 
7276     IF (AP_IMPORT_VALIDATION_PKG.v_check_receipt_info (
7277          p_invoice_rec	,			 -- IN
7278          p_invoice_lines_tab(i),                 -- IN
7279          p_default_last_updated_by,              -- IN
7280          p_default_last_update_login,            -- IN
7281          p_temp_line_status           => l_temp_line_status, -- OUT NOCOPY
7282          p_calling_sequence           => current_calling_sequence)
7283          <> TRUE) THEN
7284       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7285         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7286         'v_check_receipt_info<-' ||current_calling_sequence);
7287       END IF;
7288       RAISE check_lines_failure;
7289     END IF;
7290    END IF;
7291 
7292     --
7293     -- show output values (only if debug_switch = 'Y')
7294     --
7295     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7296       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7297                    '------------------> l_temp_line_status = '||
7298             l_temp_line_status);
7299     END IF;
7300 
7301     -- We need to set the current status to 'N' only if the temp line status
7302     -- returns 'N'. So all temp returns of 'N' will overwrite the current
7303     -- invoice status to 'N' which finally would be returned to the calling
7304     -- function.
7305     IF (l_temp_line_status = 'N') THEN
7306       l_current_invoice_status := l_temp_line_status;
7307     END IF;
7308 
7309 
7310     -----------------------------------------------------------------
7311     -- Step 11
7312     --Validate the purchasing_category information.
7313     -----------------------------------------------------------------
7314     IF (p_invoice_lines_tab(i).purchasing_category_id IS NOT NULL OR
7315          p_invoice_lines_tab(i).purchasing_category IS NOT NULL) THEN
7316 
7317       debug_info := '(Check Purchasing Category Info 11) Check if valid '
7318                     ||'purchasing category information is provided';
7319       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7320         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7321                                       debug_info);
7322       END IF;
7323 
7324       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_purch_category(
7325                 p_invoice_lines_tab(i),
7326                 p_default_last_updated_by,
7327                 p_default_last_update_login,
7328                 p_current_invoice_status => l_temp_line_status,  --IN OUT
7329                 p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
7330 
7331          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7332            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7333            'v_check_purchasing_category<-'||current_calling_sequence);
7334          END IF;
7335          RAISE check_lines_failure;
7336 
7337       END IF;
7338 
7339       IF (l_temp_line_status = 'N') THEN
7340         l_current_invoice_status := l_temp_line_status;
7341       END IF;
7342       --
7343       -- show output values (only if debug_switch = 'Y')
7344       --
7345       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7346         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7347           '------------------>
7348           l_temp_invoice_status  = '||l_temp_line_status);
7349       END IF;
7350 
7351     END IF;
7352 
7353 
7354     -----------------------------------------------------------------
7355     -- Step 12
7356     --Validate the Cost_Factor information.
7357     -----------------------------------------------------------------
7358     IF (p_invoice_lines_tab(i).cost_factor_id IS NOT NULL OR
7359          p_invoice_lines_tab(i).cost_factor_name IS NOT NULL) THEN
7360 
7361       debug_info := '(Check Cost Factor Info 12) Check if valid '
7362                     ||'cost factor information is provided';
7363       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7364         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7365                                       debug_info);
7366       END IF;
7367 
7368       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_cost_factor(
7369                 p_invoice_lines_tab(i),
7370                 p_default_last_updated_by,
7371                 p_default_last_update_login,
7372                 p_current_invoice_status => l_temp_line_status,  --IN OUT
7373                 p_calling_sequence  => current_calling_sequence) <> TRUE )THEN
7374 
7375          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7376            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7377            'v_check_line_cost_factor<-'||current_calling_sequence);
7378          END IF;
7379          RAISE check_lines_failure;
7380 
7381       END IF;
7382 
7383       IF (l_temp_line_status = 'N') THEN
7384         l_current_invoice_status := l_temp_line_status;
7385       END IF;
7386       --
7387       -- show output values (only if debug_switch = 'Y')
7388       --
7389       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7390         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7391           '------------------>
7392           l_temp_invoice_status  = '||l_temp_line_status);
7393       END IF;
7394 
7395     END IF;
7396 
7397 
7398     -------------------------------------------------------
7399     --bugfix:5565310
7400     --Step 12a
7401     --Populate PO Tax Attributes on the line if it is a po/rct
7402     --matched.
7403     ----------------------------------------------------------
7404     IF(p_invoice_lines_tab(i).po_line_location_id IS NOT NULL) THEN
7405 
7406        IF (v_check_line_get_po_tax_attr(p_invoice_rec  =>  p_invoice_rec,
7407        				      p_invoice_lines_rec =>p_invoice_lines_tab(i),
7408 				      p_calling_sequence => current_calling_sequence)
7409 				      <> TRUE) THEN
7410 
7411             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7412 	            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7413 		              'v_check_line_populate_po_tax_attr<-' ||current_calling_sequence);
7414             END IF;
7415             RAISE check_lines_failure;
7416 
7417        END IF;
7418 
7419     END IF;
7420     --------------------------------------------------------
7421     -- Step 13
7422     -- check for accounting date Information
7423     ---------------------------------------------------------
7424     debug_info := '(Check_lines 13) Call v_check_line_accounting_date';
7425     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7426       AP_IMPORT_UTILITIES_PKG.Print(
7427         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
7428     END IF;
7429 
7430     IF (AP_IMPORT_VALIDATION_PKG.v_check_line_accounting_date(
7431          p_invoice_rec,                          -- IN
7432          p_invoice_lines_tab(i),                -- IN OUT NOCOPY
7433          p_gl_date_from_get_info,                -- IN
7434          p_gl_date_from_receipt_flag,            -- IN
7435          p_set_of_books_id,                      -- IN
7436          p_purch_encumbrance_flag,               -- IN
7437          p_default_last_updated_by,              -- IN
7438          p_default_last_update_login,            -- IN
7439          p_current_invoice_status   => l_temp_line_status,-- IN OUT NOCOPY
7440          p_calling_sequence         => current_calling_sequence)
7441          <> TRUE )THEN
7442       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7443         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7444           'v_check_line_accounting_date<-' ||current_calling_sequence);
7445       END IF;
7446       RAISE check_lines_failure;
7447     END IF;
7448 
7449     --
7450     -- show output values (only if debug_switch = 'Y')
7451     --
7452     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7453       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7454       '------------------> l_temp_line_status = '|| l_temp_line_status);
7455     END IF;
7456     --
7457     IF (l_temp_line_status = 'N') THEN
7458       l_current_invoice_status := l_temp_line_status;
7459     END IF;
7460 
7461 
7462     --------------------------------------------------------
7463     -- Step 14
7464     -- check for project information
7465     ---------------------------------------------------------
7466     debug_info := '(Check_lines 14) Call v_check_line_project_info';
7467     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7468       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7469                                     debug_info);
7470     END IF;
7471 
7472     --bugfix:4773191 , added the IF condition to bypass the pa flexbuild
7473     --validation since this is already done in OIE during the creation
7474     --of expense report before populating the records into interface table.
7475     IF (p_invoice_rec.invoice_type_lookup_code <> 'EXPENSE REPORT') THEN
7476        l_pa_built_account := 0;
7477 
7478        IF (AP_IMPORT_VALIDATION_PKG.v_check_line_project_info (
7479          p_invoice_rec,                              -- IN
7480          p_invoice_lines_tab(i),                        -- IN OUT NOCOPY
7481          nvl(p_invoice_lines_tab(i).accounting_date, --  IN p_accounting_date
7482              p_gl_date_from_get_info),
7483          p_pa_installed,                             -- IN
7484          l_employee_id,                              -- IN
7485          p_base_currency_code,                         -- IN
7486          p_set_of_books_id,                           -- IN
7487          p_chart_of_accounts_id,                     -- IN
7488          p_default_last_updated_by,                     -- IN
7489          p_default_last_update_login,                 -- IN
7490          p_pa_built_account         => l_pa_built_account, -- OUT NOCOPY
7491          p_current_invoice_status   => l_temp_line_status, -- IN OUT NOCOPY
7492          p_calling_sequence         => current_calling_sequence)
7493          <> TRUE )THEN
7494          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7495             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7496               'v_check_line_project_info<-' ||current_calling_sequence);
7497          END IF;
7498          RAISE check_lines_failure;
7499        END IF;
7500 
7501        --
7502        -- show output values (only if debug_switch = 'Y')
7503        --
7504        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7505           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7506              '------------------> l_temp_line_status = '|| l_temp_line_status
7507             ||' dist_code_combination_id = '
7508             || to_char(p_invoice_lines_tab(i).dist_code_combination_id));
7509        END IF;
7510        --
7511        --
7512        IF (l_temp_line_status = 'N') THEN
7513           l_current_invoice_status := l_temp_line_status;
7514        END IF;
7515 
7516     END IF; --bugfix:4773191
7517 
7518     -------------------------------------------------------------------
7519     -- Step 15.0
7520     -- Check for Product Registration in AP_PRODUCT_REGISTRATIONS
7521     -- If source application is registered for DISTRIBUTION_GENERATION
7522     -- then no need to validate lien account info
7523     -------------------------------------------------------------------
7524 
7525     debug_info := '(Check_lines 15.0) Call Is_Product_Registered';
7526     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7527        AP_IMPORT_UTILITIES_PKG.Print(
7528             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
7529     End if;
7530 
7531     /* bug 5039042. Whether Source Application is registered for
7532        Distribution Generation Via Ap_Product_Registrations */
7533     /* Bug 5448579. Added the IF condition */
7534     IF (p_invoice_lines_tab(i).application_id IS NULL) THEN
7535       l_product_registered := 'N';
7536     ELSE
7537       IF (Ap_Import_Utilities_Pkg.Is_Product_Registered(
7538                 P_application_id => p_invoice_lines_tab(i).application_id,
7539                 X_registration_api    => l_dummy,
7540                 X_registration_view   => l_dummy,
7541                 P_calling_sequence    => current_calling_sequence)) THEN
7542         l_product_registered := 'Y';
7543       ELSE
7544         l_product_registered := 'N';
7545       END IF;
7546     END IF;
7547 
7548    /* bug 5121735 */
7549    debug_info := '(Check_lines 15.1) l_product_registered: '||l_product_registered;
7550    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7551      AP_IMPORT_UTILITIES_PKG.Print(
7552      AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
7553    End if;
7554 
7555     -------------------------------------------------------------------
7556     -- Step 15
7557     -- check for account Information.
7558     -- Retropricing: The account validation is not needed for PPA
7559     -- as the ccid will be copied from the corrected_invoice_dist or from
7560     -- po/rcv transaction
7561     ------------------------------------------------------------------
7562     /* bug 5039042. If Source Application is registered for
7563        Ditribution Generation Via Ap_Product_Registrations
7564        Then no need to validate the line account info */
7565 
7566     IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
7567       IF (l_product_registered = 'N') THEN   /* bug 5121735 */
7568         debug_info := '(Check_lines 15) Call v_check_line_account_info';
7569         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7570           AP_IMPORT_UTILITIES_PKG.Print(
7571             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
7572         End if;
7573 
7574         /*Start of bug 4386299*/
7575         --If distribution_set_id is null or accounting information is not there
7576         --then we would default from vendor-sites
7577         IF (
7578             (p_invoice_lines_tab(i).dist_code_concatenated IS NULL
7579             OR p_invoice_lines_tab(i).partial_segments = 'Y')
7580         AND p_invoice_lines_tab(i).dist_code_combination_id IS NULL
7581         AND p_invoice_rec.po_number IS NULL                 --default po number
7582         AND p_invoice_lines_tab(i).po_number IS NULL
7583         AND p_invoice_lines_tab(i).po_header_id IS NULL
7584         AND p_invoice_lines_tab(i).distribution_set_id IS NULL
7585         AND p_invoice_lines_tab(i).distribution_set_name IS NULL
7586         AND (p_invoice_rec.vendor_id IS NOT NULL
7587             AND p_invoice_rec.vendor_site_id IS NOT NULL)
7588         )
7589         THEN
7590           begin
7591             select distribution_set_id
7592               into p_invoice_lines_tab(i).distribution_set_id
7593               from po_vendor_sites
7594              where vendor_id=p_invoice_rec.vendor_id
7595                and vendor_site_id=p_invoice_rec.vendor_site_id;
7596           exception
7597            when no_data_found then
7598             p_invoice_lines_tab(i).distribution_set_id:=null;
7599           end;
7600         END IF;
7601         /*End of bug 4386299*/
7602 
7603             IF (AP_IMPORT_VALIDATION_PKG.v_check_line_account_info (
7604              p_invoice_lines_tab(i),                       -- IN OUT NOCOPY
7605              p_freight_code_combination_id,                -- IN
7606              l_pa_built_account,                        -- IN
7607              nvl(p_invoice_lines_tab(i).accounting_date, -- IN p_accounting_date
7608                  p_gl_date_from_get_info),
7609              p_set_of_books_id,                          -- IN
7610              p_chart_of_accounts_id,                       -- IN
7611              p_default_last_updated_by,                    -- IN
7612              p_default_last_update_login,                -- IN
7613              p_current_invoice_status => l_temp_line_status,-- IN OUT NOCOPY
7614              p_calling_sequence       => current_calling_sequence) <> TRUE
7615              ) THEN
7616           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7617              AP_IMPORT_UTILITIES_PKG.Print(
7618                AP_IMPORT_INVOICES_PKG.g_debug_switch,
7619                  'v_check_line_account_info<-' ||current_calling_sequence);
7620           END IF;
7621           RAISE check_lines_failure;
7622         END IF;
7623         --
7624         -- show output values (only if debug_switch = 'Y')
7625         --
7626         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7627           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7628             '------------------> l_temp_line_status = '||
7629             l_temp_line_status ||'dist_code_combination_id = '
7630             ||to_char(p_invoice_lines_tab(i).dist_code_combination_id));
7631         END IF;
7632         --
7633         IF (l_temp_line_status = 'N') THEN
7634           l_current_invoice_status := l_temp_line_status;
7635         END IF;
7636      END IF;  -- l_product_registered /* bug 5121735 */
7637     END IF;  --source <> PPA
7638 
7639     --------------------------------------------------------------------------
7640     -- Step 16
7641     -- check for deferred accounting Information
7642     -- Retropricing: For PPA Lines deferred_acctg_flag = 'N' and the validation
7643     -- w.r.t deferred accounting is not required.
7644     --------------------------------------------------------------------------
7645     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
7646 
7647         debug_info := '(Check_lines 16) Call v_check_deferred_accounting';
7648         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7649           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7650                                          debug_info);
7651         END IF;
7652 
7653         IF (AP_IMPORT_VALIDATION_PKG.v_check_deferred_accounting (
7654              p_invoice_lines_tab(i),                     -- IN OUT NOCOPY
7655              p_set_of_books_id,                        -- IN
7656              p_default_last_updated_by,                -- IN
7657              p_default_last_update_login,              -- IN
7658              p_current_invoice_status => l_temp_line_status,-- IN OUT NOCOPY
7659              p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
7660           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7661             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7662             'v_check_deferred_accounting<-' ||current_calling_sequence);
7663           end if;
7664           RAISE check_lines_failure;
7665         END IF;
7666 
7667         --
7668         -- show output values (only if debug_switch = 'Y')
7669         --
7670         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7671           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7672              '------------------> l_temp_line_status = '||
7673             l_temp_line_status);
7674         END IF;
7675         --
7676         IF (l_temp_line_status = 'N') THEN
7677           l_current_invoice_status := l_temp_line_status;
7678         END IF;
7679 
7680     END IF; --source <> PPA
7681     --------------------------------------------------------
7682     -- Step 17
7683     -- check distribution set information
7684     -- Retropricing: For PPA Lines dist set is NULL and the validation
7685     -- w.r.t Dist Set is not required.
7686     ---------------------------------------------------------
7687      IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
7688         --
7689         debug_info := '(Check_lines 17) Call v_check_line_dist_set';
7690         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7691           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7692                                         debug_info);
7693         END IF;
7694         --
7695         IF (nvl(p_invoice_lines_tab(i).line_type_lookup_code, 'ITEM' )
7696              = 'ITEM') THEN
7697           IF  (AP_IMPORT_VALIDATION_PKG.v_check_line_dist_set (
7698                p_invoice_rec,                         -- IN
7699                p_invoice_lines_tab(i),                -- IN OUT NOCOPY
7700                p_base_currency_code,                  -- IN
7701                l_employee_id,                         -- IN
7702                p_gl_date_from_get_info,               -- IN
7703                p_set_of_books_id,                     -- IN
7704                p_chart_of_accounts_id,                -- IN
7705                p_pa_installed,                        -- IN
7706                p_default_last_updated_by,             -- IN
7707                p_default_last_update_login,           -- IN
7708                p_current_invoice_status   => l_temp_line_status,-- IN OUT NOCOPY
7709                p_calling_sequence         => current_calling_sequence)
7710               <> TRUE )THEN
7711             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
7712              AP_IMPORT_UTILITIES_PKG.Print(
7713                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
7714                       'v_check_line_dist_set<-' ||current_calling_sequence);
7715             END IF;
7716             RAISE check_lines_failure;
7717           END IF;
7718           --
7719           -- show output values (only if debug_switch = 'Y')
7720           --
7721           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
7722             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7723              '------------------> l_temp_line_status = '|| l_temp_line_status);
7724           END IF;
7725           --
7726           IF (l_temp_line_status = 'N') THEN
7727         l_current_invoice_status := l_temp_line_status;
7728           END IF;
7729         END IF; -- Check dist set info, only for ITEM type lines.
7730         --
7731     END IF; --source <> PPA
7732 
7733    --------------------------------------------------------
7734    -- Step 18
7735    -- Validate Qty related information for non PO/RCV matched lines
7736    ---------------------------------------------------------
7737    debug_info := '(Check_lines 18) Call v_check_qty_uom_info';
7738    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7739      AP_IMPORT_UTILITIES_PKG.Print(
7740          AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
7741    END IF;
7742 
7743    -- check for invalid qty related information for non PO/RCV matched lines
7744    IF (AP_IMPORT_VALIDATION_PKG.v_check_qty_uom_non_po (
7745          p_invoice_rec,                     -- IN
7746          p_invoice_lines_tab(i),               -- IN OUT NOCOPY
7747          p_default_last_updated_by,          -- IN
7748          p_default_last_update_login,        -- IN
7749          p_current_invoice_status   => l_temp_line_status,  -- IN OUT NOCOPY
7750          p_calling_sequence         => current_calling_sequence) <> TRUE) THEN
7751      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7752        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7753            'v_check_invalid_awt_group<-' ||current_calling_sequence);
7754      END IF;
7755      RAISE check_lines_failure;
7756    END IF;
7757    --
7758    -- show output values (only if debug_switch = 'Y')
7759    --
7760    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7761      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7762       '------------------> l_temp_line_status = '|| l_temp_line_status);
7763    END IF;
7764 
7765    --
7766    IF (l_temp_line_status = 'N') THEN
7767      l_current_invoice_status := l_temp_line_status;
7768    END IF;
7769 
7770 
7771    --------------------------------------------------------
7772    -- Step 19
7773    -- check for AWT group
7774    ---------------------------------------------------------
7775    debug_info := '(Check_lines 19) Call v_check_invalid_awt_group';
7776     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7777      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7778      debug_info);
7779     END IF;
7780 
7781    -- check for invalid AWT group
7782    IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_awt_group(
7783        p_invoice_rec,                              -- IN
7784        p_invoice_lines_tab(i),                     -- IN OUT NOCOPY
7785        p_default_last_updated_by,                -- IN
7786        p_default_last_update_login,               -- IN
7787        p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
7788        p_calling_sequence          => current_calling_sequence) <> TRUE )THEN
7789      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7790        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7791        'v_check_invalid_awt_group<-' ||current_calling_sequence);
7792      END IF;
7793      RAISE check_lines_failure;
7794    END IF;
7795    --
7796    -- show output values (only if debug_switch = 'Y')
7797    --
7798    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7799      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7800        '------------------> l_temp_line_status = '|| l_temp_line_status);
7801    END IF;
7802    --
7803    IF (l_temp_line_status = 'N') THEN
7804      l_current_invoice_status := l_temp_line_status;
7805    END IF;
7806 
7807    --bug6639866
7808    --------------------------------------------------------
7809    -- Step 19.1
7810    -- check for pay AWT group
7811    ---------------------------------------------------------
7812    debug_info := '(Check_lines 19) Call v_check_invalid_line_pay_awt_g';
7813     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7814      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7815      debug_info);
7816     END IF;
7817 
7818    -- check for invalid AWT group
7819    IF (AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_pay_awt_g(
7820        p_invoice_rec,                              -- IN
7821        p_invoice_lines_tab(i),                     -- IN OUT NOCOPY
7822        p_default_last_updated_by,                -- IN
7823        p_default_last_update_login,               -- IN
7824        p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
7825        p_calling_sequence          => current_calling_sequence) <> TRUE )THEN
7826      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7827        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7828        'v_check_invalid_pay_awt_group<-' ||current_calling_sequence);
7829      END IF;
7830      RAISE check_lines_failure;
7831    END IF;
7832    --
7833    -- show output values (only if debug_switch = 'Y')
7834    --
7835    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7836      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7837        '------------------> l_temp_line_status = '|| l_temp_line_status);
7838    END IF;
7839    --
7840    IF (l_temp_line_status = 'N') THEN
7841      l_current_invoice_status := l_temp_line_status;
7842    END IF;
7843 
7844 
7845 
7846 
7847    --------------------------------------------------------
7848    -- Step 20
7849    -- check for Duplicate Line Num
7850    -- Retropricing: This check is not needed for PPA's
7851    ---------------------------------------------------------
7852    IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
7853        debug_info := '(Check_lines 20) Call v_check_duplicate_line_num';
7854        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7855          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7856                                        debug_info);
7857        END IF;
7858 
7859        IF (AP_IMPORT_VALIDATION_PKG.v_check_duplicate_line_num(
7860              p_invoice_rec,                          -- IN
7861              p_invoice_lines_tab(i),                 -- IN OUT NOCOPY
7862              p_default_last_updated_by,              -- IN
7863              p_default_last_update_login,            -- IN
7864              p_current_invoice_status     => l_temp_line_status,-- IN OUT
7865              p_calling_sequence           => current_calling_sequence)
7866              <> TRUE )THEN
7867           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7868            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7869              'v_check_duplicate_line_num<-' ||current_calling_sequence);
7870           END IF;
7871           RAISE check_lines_failure;
7872        END IF;
7873        --
7874        -- show output values (only if debug_switch = 'Y')
7875        --
7876        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7877          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7878            '------------------> l_temp_line_status = '|| l_temp_line_status);
7879        END IF;
7880        --
7881        IF (l_temp_line_status = 'N') THEN
7882          l_current_invoice_status := l_temp_line_status;
7883        ELSE
7884          IF (p_invoice_lines_tab(i).line_number is NULL) then
7885            p_invoice_lines_tab(i).line_number := l_max_line_number + 1;
7886            l_max_line_number := l_max_line_number + 1;
7887          END IF;
7888        END IF;
7889    END IF;
7890 
7891    --------------------------------------------------------
7892    -- Step 21
7893    -- check Asset Info
7894    ---------------------------------------------------------
7895    debug_info := '(Check_lines 21) Call v_check_asset_info';
7896    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7897      AP_IMPORT_UTILITIES_PKG.Print(
7898        AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
7899    End if;
7900 
7901    IF (AP_IMPORT_VALIDATION_PKG.v_check_asset_info (
7902        p_invoice_lines_tab(i),                   -- IN OUT NOCOPY
7903        p_set_of_books_id,                   -- IN
7904        P_asset_book_type,                      -- IN  VARCHAR2
7905        p_default_last_updated_by,               -- IN
7906        p_default_last_update_login,             -- IN
7907        p_current_invoice_status   => l_temp_line_status,-- IN OUT NOCOPY
7908        p_calling_sequence         => current_calling_sequence)
7909        <> TRUE) THEN
7910       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7911        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7912        'v_check_misc_line_info<-' ||current_calling_sequence);
7913       END IF;
7914       RAISE check_lines_failure;
7915    END IF;
7916    --
7917    -- show output values (only if debug_switch = 'Y')
7918    --
7919    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7920      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7921       '------------------> l_temp_line_status = '|| l_temp_line_status);
7922    END IF;
7923 
7924    --
7925    IF (l_temp_line_status = 'N') THEN
7926      l_current_invoice_status := l_temp_line_status;
7927    END IF;
7928 
7929 
7930    --------------------------------------------------------
7931    -- Step 22
7932    -- check for Misc Line Info
7933    ---------------------------------------------------------
7934    debug_info := '(Check_lines 22) Call v_check_misc_line_info';
7935    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7936      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7937                                     debug_info);
7938    END IF;
7939 
7940    IF (AP_IMPORT_VALIDATION_PKG.v_check_misc_line_info(
7941          p_invoice_rec,		            --7599916
7942          p_invoice_lines_tab(i),            -- IN OUT NOCOPY
7943          p_default_last_updated_by,         -- IN
7944          p_default_last_update_login,        -- IN
7945          p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
7946          p_calling_sequence          => current_calling_sequence)
7947         <> TRUE )THEN
7948       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7949        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7950          'v_check_misc_line_info<-' ||current_calling_sequence);
7951       END IF;
7952       RAISE check_lines_failure;
7953    END IF;
7954    --
7955    -- show output values (only if debug_switch = 'Y')
7956    --
7957    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7958      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7959         '------------------> l_temp_line_status = '||
7960         l_temp_line_status);
7961    END IF;
7962 
7963    --
7964    IF (l_temp_line_status = 'N') THEN
7965      l_current_invoice_status := l_temp_line_status;
7966    END IF;
7967 
7968    --------------------------------------------------------------------------
7969    -- Step 23
7970    -- Check for Tax line info.
7971    -- Retropricing: Tax line would be created by Validation or Calculate Tax
7972    -------------------------------------------------------------------------
7973    IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
7974        debug_info := '(Check_lines 23) Call v_check_tax_line_info';
7975        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7976          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7977                                         debug_info);
7978        END IF;
7979 
7980        IF (AP_IMPORT_VALIDATION_PKG.v_check_tax_line_info(
7981              p_invoice_lines_tab(i),            -- IN OUT NOCOPY
7982              p_default_last_updated_by,         -- IN
7983              p_default_last_update_login,       -- IN
7984              p_current_invoice_status    => l_temp_line_status, -- IN OUT NOCOPY
7985              p_calling_sequence          => current_calling_sequence)
7986             <> TRUE )THEN
7987           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7988            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7989              'v_check_tax_line_info<-' ||current_calling_sequence);
7990           END IF;
7991           RAISE check_lines_failure;
7992        END IF;
7993        --
7994        -- show output values (only if debug_switch = 'Y')
7995        --
7996        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
7997          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
7998             '------------------> l_temp_line_status = '||
7999                     l_temp_line_status);
8000        END IF;
8001 
8002        --
8003        IF (l_temp_line_status = 'N') THEN
8004          l_current_invoice_status := l_temp_line_status;
8005        END IF;
8006    END IF;
8007 
8008 /* Bug 4014019: Commenting the call to jg_globe_flex_val due to build issues.
8009 
8010    --------------------------------------------------------
8011    -- Step 24
8012    -- check for Invalid Line Global Flexfield
8013    ---------------------------------------------------------
8014    debug_info := '(Check Lines 24) Check for Line Global Flexfield';
8015     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8016      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8017                                    debug_info);
8018     END IF;
8019    jg_globe_flex_val.check_attr_value(
8020             'APXIIMPT',
8021             p_invoice_lines_tab(i).global_attribute_category,
8022             p_invoice_lines_tab(i).global_attribute1,
8023             p_invoice_lines_tab(i).global_attribute2,
8024             p_invoice_lines_tab(i).global_attribute3,
8025             p_invoice_lines_tab(i).global_attribute4,
8026             p_invoice_lines_tab(i).global_attribute5,
8027             p_invoice_lines_tab(i).global_attribute6,
8028             p_invoice_lines_tab(i).global_attribute7,
8029             p_invoice_lines_tab(i).global_attribute8,
8030             p_invoice_lines_tab(i).global_attribute9,
8031             p_invoice_lines_tab(i).global_attribute10,
8032             p_invoice_lines_tab(i).global_attribute11,
8033             p_invoice_lines_tab(i).global_attribute12,
8034             p_invoice_lines_tab(i).global_attribute13,
8035             p_invoice_lines_tab(i).global_attribute14,
8036             p_invoice_lines_tab(i).global_attribute15,
8037             p_invoice_lines_tab(i).global_attribute16,
8038             p_invoice_lines_tab(i).global_attribute17,
8039             p_invoice_lines_tab(i).global_attribute18,
8040             p_invoice_lines_tab(i).global_attribute19,
8041             p_invoice_lines_tab(i).global_attribute20,
8042             TO_CHAR(p_set_of_books_id),
8043             fnd_date.date_to_canonical(p_invoice_rec.invoice_date),
8044             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,   -- Retropricing: global need to modify
8045             TO_CHAR(p_invoice_lines_tab(i).invoice_line_id),-- the API to handle PPA tables.
8046             TO_CHAR(p_default_last_updated_by),
8047             TO_CHAR(p_default_last_update_login),
8048             current_calling_sequence,
8049             NULL,NULL,
8050             p_invoice_lines_tab(i).line_type_lookup_code,
8051             NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,
8052             NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,NULL,
8053             p_current_status => l_temp_line_status);
8054 
8055 
8056     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8057       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8058      'Global Flexfield Lines Processed '|| l_temp_line_status);
8059       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8060          '------------------> l_temp_line_status = '||l_temp_line_status);
8061     END IF;
8062 
8063     IF (l_temp_line_status = 'N') THEN
8064       l_current_invoice_status := l_temp_line_status;
8065     END IF;
8066 
8067 */
8068 
8069     --------------------------------------------------------
8070     -- Step 25
8071     -- Check proration information for non item lines
8072     -- Retropricing: The code below won't be executed for PPA
8073     -- Lines as the prorate_across_flag is N  for RETROITEM
8074     ---------------------------------------------------------
8075     debug_info := '(Check Lines 25) Checking the total dist amount to be '
8076                    ||'prorated';
8077     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8078      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8079                                    debug_info);
8080     END IF;
8081 
8082     IF (nvl(p_invoice_lines_tab(i).line_type_lookup_code,'ITEM') <> 'ITEM' AND
8083         nvl(p_invoice_lines_tab(i).prorate_across_flag,'N') = 'Y')  THEN
8084       IF (AP_IMPORT_VALIDATION_PKG.v_check_prorate_info (
8085              p_invoice_rec,                                 -- IN
8086              p_invoice_lines_tab(i),                        -- IN OUT NOCOPY
8087              p_default_last_updated_by,                     -- IN
8088              p_default_last_update_login,                   -- IN
8089              p_current_invoice_status  =>l_temp_line_status,-- IN OUT NOCOPY
8090              p_calling_sequence        => current_calling_sequence)
8091              <> TRUE )THEN
8092         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8093           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8094           'v_check_prorate_info<-' ||current_calling_sequence);
8095         END IF;
8096         RAISE check_lines_failure;
8097       END IF;
8098       --
8099       -- show output values (only if debug_switch = 'Y')
8100       --
8101       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8102         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8103            '------------------> l_temp_line_status = '||l_temp_line_status);
8104       END IF;
8105 
8106       --
8107       IF (l_temp_line_status = 'N') THEN
8108         l_current_invoice_status := l_temp_line_status;
8109       END IF;
8110 
8111     END IF; -- End for line type <> ITEM and prorate = Y
8112 
8113     --------------------------------------------------------
8114     -- Step 26
8115     -- Check if retainage account is available if the po shipment
8116     -- has retainage.
8117     ---------------------------------------------------------
8118     IF (p_invoice_lines_tab(i).po_line_location_id IS NOT NULL AND
8119         nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'PREPAYMENT') THEN
8120 
8121 	debug_info := '(Check Lines 26) Checking for retainage account ';
8122 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8123 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8124 	END IF;
8125 
8126 	IF (AP_IMPORT_VALIDATION_PKG.v_check_line_retainage(
8127 		p_invoice_lines_tab(i),				-- IN OUT
8128 		p_retainage_ccid,
8129 		p_default_last_updated_by,
8130 		p_default_last_update_login,
8131 		p_current_invoice_status => l_temp_line_status, -- IN OUT
8132 		p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
8133 
8134 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8135 		    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8136                                                   'v_check_line_retainage<-' ||current_calling_sequence);
8137 		END IF;
8138 		RAISE check_lines_failure;
8139 	END IF;
8140 
8141 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8142 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8143 					  '------------------> l_temp_line_status = '|| l_temp_line_status);
8144 	END IF;
8145 
8146 	IF (l_temp_line_status = 'N') THEN
8147 		l_current_invoice_status := l_temp_line_status;
8148 	END IF;
8149     END IF;
8150 
8151     -- bug 6989166 start
8152     --------------------------------------------------------
8153     -- Step 27
8154     -- Check valid ship to location code, when ship to
8155     -- location id is null.
8156     ---------------------------------------------------------
8157     IF (p_invoice_lines_tab(i).ship_to_location_code IS NOT NULL AND
8158 		p_invoice_lines_tab(i).ship_to_location_id IS NULL) THEN
8159 
8160 	debug_info := '(Check Lines 27) Checking for ship to location code ';
8161 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8162 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
8163 	END IF;
8164 
8165 	IF (AP_IMPORT_VALIDATION_PKG.v_check_ship_to_location_code(
8166 		p_invoice_rec,
8167 		p_invoice_lines_tab(i),
8168 		p_default_last_updated_by,
8169 		p_default_last_update_login,
8170 		p_current_invoice_status => l_temp_line_status, -- IN OUT
8171 		p_calling_sequence       => current_calling_sequence) <> TRUE )THEN
8172 
8173 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8174 		    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8175                                                   'v_check_ship_to_location_code<-' ||current_calling_sequence);
8176 		END IF;
8177 		RAISE check_lines_failure;
8178 	END IF;
8179 
8180 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8181 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8182 					  '------------------> ship_to_location_id = '
8183 					  || p_invoice_lines_tab(i).ship_to_location_id);
8184 	END IF;
8185 
8186 	IF (l_temp_line_status = 'N') THEN
8187 		l_current_invoice_status := l_temp_line_status;
8188 	END IF;
8189 
8190     END IF;
8191 
8192     -- bug 6989166 end
8193 
8194   END LOOP; -- for lines
8195 
8196   p_current_invoice_status := l_current_invoice_status;
8197   RETURN (TRUE);
8198 
8199 EXCEPTION
8200   WHEN OTHERS THEN
8201     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8202      AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8203                                    debug_info);
8204     END IF;
8205 
8206     IF (SQLCODE < 0) then
8207       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8208        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8209                                      SQLERRM);
8210       END IF;
8211     END IF;
8212 
8213     IF (invoice_lines%ISOPEN) THEN
8214        CLOSE invoice_lines;
8215     END IF;
8216     RETURN (FALSE);
8217 
8218 END v_check_lines_validation;
8219 
8220 -----------------------------------------------------------------------------
8221 -- This function is used to validate the precision of a line amount.
8222 --
8223 FUNCTION v_check_invoice_line_amount (
8224          p_invoice_lines_rec          IN AP_IMPORT_INVOICES_PKG.r_line_info_rec,
8225          p_precision_inv_curr           IN            NUMBER,
8226          p_default_last_updated_by      IN            NUMBER,
8227          p_default_last_update_login    IN            NUMBER,
8228          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
8229          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
8230 IS
8231 
8232 check_lines_failure        EXCEPTION;
8233 debug_info                 VARCHAR2(250);
8234 current_calling_sequence   VARCHAR2(2000);
8235 l_current_invoice_status   VARCHAR2(1)    :='Y';
8236 
8237 BEGIN
8238 
8239   -- Updating the calling sequence
8240   current_calling_sequence :=
8241      'AP_IMPORT_VALIDATION_PKG.v_check_invoice_line_amount<-'
8242      ||P_calling_sequence;
8243 
8244   IF LENGTH((ABS(p_invoice_lines_rec.amount) -
8245              TRUNC(ABS(p_invoice_lines_rec.amount))))-1  >
8246      NVL(p_precision_inv_curr,0) THEN
8247 
8248     debug_info :=
8249       '(Check Invoice Line Amount 1) Lines amount exceeds precision.';
8250     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8251       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8252                                     debug_info);
8253     END IF;
8254 
8255     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
8256           (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8257                p_invoice_lines_rec.invoice_line_id,
8258                'LINE AMOUNT EXCEEDS PRECISION',
8259                p_default_last_updated_by,
8260             p_default_last_update_login,
8261             current_calling_sequence) <> TRUE) THEN
8262       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8263         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8264           'insert_rejections<-'||current_calling_sequence);
8265       END IF;
8266       RAISE check_lines_failure;
8267     END IF;
8268     l_current_invoice_status :='N';
8269   END IF;
8270 
8271   p_current_invoice_status := l_current_invoice_status;
8272 
8273   RETURN (TRUE);
8274 
8275 EXCEPTION
8276   WHEN OTHERS THEN
8277     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8278       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8279                                     debug_info);
8280     END IF;
8281 
8282     IF (SQLCODE < 0) then
8283       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8284         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8285                                       SQLERRM);
8286       END IF;
8287     END IF;
8288     RETURN(FALSE);
8289 
8290 END v_check_invoice_line_amount;
8291 
8292 
8293 -----------------------------------------------------------------------------
8294 -- This function is used to validate PO information at line level.
8295 --
8296 FUNCTION v_check_line_po_info (
8297          p_invoice_rec
8298            IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
8299          p_invoice_lines_rec
8300            IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
8301          p_set_of_books_id              IN            NUMBER,
8302          p_positive_price_tolerance     IN            NUMBER,
8303          p_qty_ord_tolerance            IN            NUMBER,
8304 	 p_amt_ord_tolerance		IN	      NUMBER,
8305          p_max_qty_ord_tolerance        IN            NUMBER,
8306 	 p_max_amt_ord_tolerance	IN	      NUMBER,
8307          p_default_last_updated_by      IN            NUMBER,
8308          p_default_last_update_login    IN            NUMBER,
8309          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
8310          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
8311 
8312 
8313 IS
8314 
8315 check_po_failure                   EXCEPTION;
8316 l_po_number                           VARCHAR2(20) := p_invoice_lines_rec.po_number;
8317 l_po_header_id                    NUMBER := p_invoice_lines_rec.po_header_id;
8318 l_po_line_id                    NUMBER := p_invoice_lines_rec.po_line_id;
8319 l_po_release_id                    NUMBER := p_invoice_lines_rec.po_release_id;
8320 l_po_line_location_id            NUMBER := p_invoice_lines_rec.po_line_location_id;
8321 l_po_distribution_id            NUMBER := p_invoice_lines_rec.po_distribution_id;
8322 l_match_option                    VARCHAR2(25);
8323 l_calc_quantity_invoiced        NUMBER;
8324 l_calc_unit_price               NUMBER;
8325 l_po_is_valid_flag                   VARCHAR2(1) := 'N';
8326 l_po_is_consistent_flag         VARCHAR2(1) := 'N';
8327 l_po_line_is_valid_flag            VARCHAR2(1) := 'N';
8328 l_po_line_is_consistent_flag    VARCHAR2(1) := 'N';
8329 l_po_release_is_valid_flag      VARCHAR2(1)    := 'N';
8330 l_po_rel_is_consistent_flag     VARCHAR2(1) := 'N';
8331 l_po_shipment_is_valid_flag     VARCHAR2(1)    := 'N';
8332 l_po_shipment_is_consis_flag    VARCHAR2(1) := 'N';
8333 l_po_dist_is_valid_flag            VARCHAR2(1)    := 'N';
8334 l_po_dist_is_consistent_flag    VARCHAR2(1) := 'N';
8335 l_po_inv_curr_is_consis_flag    VARCHAR2(1)    := 'N';
8336 l_current_invoice_status        VARCHAR2(1) := 'Y';
8337 l_po_is_not_blanket             VARCHAR2(1) := 'N';
8338 l_vendor_id                        NUMBER;
8339 l_purchasing_category_id	AP_INVOICE_LINES_ALL.PURCHASING_CATEGORY_ID%TYPE;
8340 current_calling_sequence         VARCHAR2(2000);
8341 debug_info                       VARCHAR2(500);
8342 
8343 -- Contextual Information for XML Gateway
8344 l_po_currency_code              VARCHAR2(15) := '';
8345 l_invoice_vendor_name           po_vendors.vendor_name%TYPE := '';
8346 
8347 l_price_correct_inv_id          NUMBER;
8348 l_pc_inv_valid                  VARCHAR2(1);
8349 l_base_match_amount		NUMBER;
8350 l_base_match_quantity		NUMBER;
8351 l_correction_amount		NUMBER;
8352 l_match_basis    		PO_LINE_TYPES.MATCHING_BASIS%TYPE;
8353 l_pc_po_amt_billed              NUMBER;
8354 l_line_amt_calculated           NUMBER;
8355 l_total_amount_invoiced		NUMBER;
8356 l_total_quantity_invoiced	NUMBER;
8357 l_total_amount_billed		NUMBER;
8358 l_total_quantity_billed		NUMBER;
8359 l_correction_dist_amount	NUMBER;
8360 l_shipment_finally_closed	VARCHAR2(1);
8361 l_corrupt_po_distributions      NUMBER;
8362 l_calc_line_amount		NUMBER;
8363 l_accrue_on_receipt_flag        po_line_locations.accrue_on_receipt_flag%TYPE;
8364 l_temp_match_option             VARCHAR2(25); --Bug5225547
8365 
8366 BEGIN
8367   -- Update the calling sequence
8368   --
8369   current_calling_sequence :=
8370     'AP_IMPORT_VALIDATION_PKG.v_check_line_po_info<-'
8371     ||P_calling_sequence;
8372 
8373 IF (nvl(p_invoice_lines_rec.line_type_lookup_code, 'ITEM' )
8374          IN ('ITEM','RETROITEM')) THEN
8375   -----------------------------------------------------------
8376   -- Case 1.0,  Default PO Number from Invoice Header if
8377   -- po_header_id and po_number are null
8378   -----------------------------------------------------------
8379   IF ((l_po_header_id IS NULL) and
8380       (p_invoice_lines_rec.po_number IS NULL) and
8381       (p_invoice_rec.po_number is NOT NULL)) THEN
8382     --
8383     debug_info := '(v_check_line_po_info 1) Default PO Number from invoice '
8384                   ||'header and get l_po_header_id';
8385     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8386       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8387                                     debug_info);
8388     END IF;
8389     --
8390 
8391     BEGIN
8392       SELECT 'Y', po_header_id
8393         INTO l_po_is_valid_flag, l_po_header_id
8394         FROM po_headers
8395        WHERE segment1 = p_invoice_rec.po_number
8396     AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
8397     /* BUG 2902452 added*/
8398     AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
8399 
8400     EXCEPTION
8401       WHEN NO_DATA_FOUND THEN
8402         -- po number is invalid
8403         -- set contextual information for XML GATEWAY
8404         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
8405                                (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8406                                 p_invoice_lines_rec.invoice_line_id,
8407                                 'INVALID PO NUM',
8408                                 p_default_last_updated_by,
8409                                 p_default_last_update_login,
8410                                 current_calling_sequence,
8411                                 'Y',
8412                                 'PO NUMBER',
8413                                 p_invoice_rec.po_number) <> TRUE) THEN
8414           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8415             AP_IMPORT_UTILITIES_PKG.Print(
8416             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8417             'insert_rejections<-'||current_calling_sequence);
8418           END IF;
8419           RAISE check_po_failure;
8420 
8421         END IF;
8422         l_current_invoice_status := 'N';
8423     END;
8424 
8425   END IF;
8426 
8427   -----------------------------------------------------------
8428   -- Case 1.1,  Reject if po_header_id is invalid
8429   -----------------------------------------------------------
8430   IF (l_po_header_id IS NOT NULL) THEN
8431       --
8432     BEGIN
8433       debug_info := '(v_check_line_po_info 1) Validate po_header_id';
8434       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8435         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8436                                       debug_info);
8437       END IF;
8438       --
8439       SELECT 'Y'
8440         INTO l_po_is_valid_flag
8441         FROM po_headers ph
8442        WHERE ph.po_header_id = l_po_header_id
8443        AND ph.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
8444       /* BUG 2902452 added */
8445        AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
8446 
8447     EXCEPTION
8448       WHEN NO_DATA_FOUND THEN
8449         -- po header id is invalid
8450         -- set  contextual information for XML GATEWAY
8451         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
8452                                (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8453                                 p_invoice_lines_rec.invoice_line_id,
8454                                 'INVALID PO NUM',
8455                                 p_default_last_updated_by,
8456                                 p_default_last_update_login,
8457                                 current_calling_sequence,
8458                                 'Y',
8459                                 'PO NUMBER',
8460                                 p_invoice_lines_rec.po_number) <> TRUE) THEN
8461           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8462             AP_IMPORT_UTILITIES_PKG.Print(
8463             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8464             'insert_rejections<-'||current_calling_sequence);
8465           END IF;
8466           RAISE check_po_failure;
8467         END IF;
8468 
8469         l_current_invoice_status := 'N';
8470     END;
8471 
8472   END IF;
8473 
8474   -----------------------------------------------------------
8475   -- Case 2, Reject if po_number is invalid
8476   -----------------------------------------------------------
8477   IF ((p_invoice_lines_rec.po_number IS NOT NULL) AND
8478       (l_po_header_id IS NULL)) THEN
8479       --
8480     BEGIN
8481       debug_info := '(v_check_line_po_info 2) Validate po_number';
8482       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8483         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8484                                       debug_info);
8485       END IF;
8486       --
8487       SELECT 'Y', ph.po_header_id
8488         INTO l_po_is_valid_flag, l_po_header_id
8489         FROM po_headers ph
8490        WHERE segment1 = p_invoice_lines_rec.po_number
8491          AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
8492       /*BUG 2902452 added*/
8493       AND nvl(authorization_status,'INCOMPLETE') in ('APPROVED','REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
8494 
8495     EXCEPTION
8496       WHEN NO_DATA_FOUND THEN
8497         -- po number is invalid
8498         -- set contextual information for XML GATEWAY
8499         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
8500                                (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8501                                 p_invoice_lines_rec.invoice_line_id,
8502                                 'INVALID PO NUM',
8503                                 p_default_last_updated_by,
8504                                 p_default_last_update_login,
8505                                 current_calling_sequence,
8506                                 'Y',
8507                                 'PO NUMBER',
8508                                 p_invoice_lines_rec.po_number) <> TRUE) THEN
8509           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8510             AP_IMPORT_UTILITIES_PKG.Print(
8511             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8512             'insert_rejections<-'||current_calling_sequence);
8513           END IF;
8514           RAISE check_po_failure;
8515         END IF;
8516 
8517         l_current_invoice_status := 'N';
8518     END;
8519 
8520   END IF;
8521 
8522   ---------------------------------------------------------------------------
8523   -- Case 3, Reject if po_header_id and po_number is inconsistent
8524   ---------------------------------------------------------------------------
8525   IF ((l_po_header_id IS NOT NULL) AND
8526       (p_invoice_lines_rec.po_number IS NOT NULL)) THEN
8527     --
8528     BEGIN
8529       debug_info := '(v_check_line_po_info 3) Check inconsistence for '
8530                     ||'po_number and po_header_id';
8531       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8532         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8533                                       debug_info);
8534       END IF;
8535       --
8536       SELECT 'Y'
8537         INTO l_po_is_consistent_flag
8538         FROM po_headers ph
8539        WHERE segment1 = p_invoice_lines_rec.po_number
8540          AND po_header_id = l_po_header_id;
8541 
8542     EXCEPTION
8543       WHEN NO_DATA_FOUND THEN
8544         -- po number is inconsistent
8545         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
8546               (AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8547                p_invoice_lines_rec.invoice_line_id,
8548                'INCONSISTENT PO INFO',
8549                p_default_last_updated_by,
8550                p_default_last_update_login,
8551                current_calling_sequence) <> TRUE) THEN
8552           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8553             AP_IMPORT_UTILITIES_PKG.Print(
8554             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8555             'insert_rejections<-'||current_calling_sequence);
8556           END IF;
8557          RAISE check_po_failure;
8558         END IF;
8559         --
8560         l_current_invoice_status := 'N';
8561     END;
8562 
8563   END IF;
8564 
8565   -----------------------------------------------------------
8566   -- Case 4,  Reject if po_line_id is invalid
8567   -----------------------------------------------------------
8568   IF (l_po_line_id IS NOT NULL) THEN
8569     --
8570     BEGIN
8571       debug_info := '(v_check_line_po_info 4) Validate po_line_id';
8572       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8573         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8574                                       debug_info);
8575       END IF;
8576       --
8577       SELECT 'Y'
8578         INTO l_po_line_is_valid_flag
8579         FROM po_lines
8580        WHERE po_line_id = l_po_line_id;
8581     EXCEPTION
8582       WHEN NO_DATA_FOUND THEN
8583         -- po line id is invalid
8584         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8585             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8586             p_invoice_lines_rec.invoice_line_id,
8587             'INVALID PO LINE NUM',
8588             p_default_last_updated_by,
8589             p_default_last_update_login,
8590             current_calling_sequence) <> TRUE) THEN
8591           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8592             AP_IMPORT_UTILITIES_PKG.Print(
8593             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8594             'insert_rejections<-'||current_calling_sequence);
8595           END IF;
8596          RAISE check_po_failure;
8597         END IF;
8598         --
8599         l_current_invoice_status := 'N';
8600     END;
8601 
8602   END IF;
8603 
8604   ------------------------------------------------------------
8605   -- Case 5, Reject if po_line_number is invalid
8606   ------------------------------------------------------------
8607   IF ((p_invoice_lines_rec.po_line_number IS NOT NULL) AND
8608       (l_po_line_id IS NULL) AND
8609       (l_po_header_id IS NOT NULL)) THEN
8610     --
8611     BEGIN
8612       debug_info := '(v_check_line_po_info 5) Validate po_line_number';
8613       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8614         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8615                                       debug_info);
8616       END IF;
8617       --
8618       --
8619       SELECT 'Y', po_line_id
8620         INTO l_po_line_is_valid_flag, l_po_line_id
8621         FROM po_lines
8622        WHERE line_num = p_invoice_lines_rec.po_line_number
8623          AND po_header_id = l_po_header_id;
8624     EXCEPTION
8625       WHEN NO_DATA_FOUND THEN
8626         -- po line number is invalid
8627         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8628             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8629             p_invoice_lines_rec.invoice_line_id,
8630             'INVALID PO LINE NUM',
8631             p_default_last_updated_by,
8632             p_default_last_update_login,
8633             current_calling_sequence) <> TRUE) THEN
8634           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8635             AP_IMPORT_UTILITIES_PKG.Print(
8636             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8637             'insert_rejections<-'||current_calling_sequence);
8638           END IF;
8639          RAISE check_po_failure;
8640         END IF;
8641         --
8642         l_current_invoice_status := 'N';
8643     END;
8644 
8645   END IF;
8646 
8647   ---------------------------------------------------------------------------
8648   -- Case 6, Reject if po_line_id and po_line_number is inconsistent
8649   ---------------------------------------------------------------------------
8650   IF ((l_po_line_id IS NOT NULL) AND
8651       (p_invoice_lines_rec.po_line_number IS NOT NULL)) THEN
8652     --
8653     BEGIN
8654       debug_info := '(v_check_line_po_info 6) Check inconsistence for '
8655                     ||'po_line_number and po_line_id';
8656       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8657         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8658                                       debug_info);
8659       END IF;
8660       --
8661       SELECT 'Y'
8662         INTO l_po_line_is_consistent_flag
8663         FROM po_lines
8664        WHERE line_num = p_invoice_lines_rec.po_line_number
8665          AND po_line_id = l_po_line_id;
8666     EXCEPTION
8667       WHEN NO_DATA_FOUND THEN
8668         -- po number is inconsistent
8669         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8670             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8671             p_invoice_lines_rec.invoice_line_id,
8672             'INCONSISTENT PO LINE INFO',
8673             p_default_last_updated_by,
8674             p_default_last_update_login,
8675             current_calling_sequence) <> TRUE) THEN
8676           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8677             AP_IMPORT_UTILITIES_PKG.Print(
8678             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8679             'insert_rejections<-'||current_calling_sequence);
8680           END IF;
8681          RAISE check_po_failure;
8682         END IF;
8683         --
8684         l_current_invoice_status := 'N';
8685     END;
8686 
8687   END IF;
8688 
8689   -----------------------------------------------------------
8690   -- Case 7,  Reject if po_release_id is invalid
8691   -----------------------------------------------------------
8692   IF (l_po_release_id IS NOT NULL) THEN
8693     --
8694     BEGIN
8695       debug_info := '(v_check_line_po_info 7) Validate po_release_id';
8696       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8697         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8698                                       debug_info);
8699       END IF;
8700       --
8701       --
8702       SELECT 'Y'
8703         INTO l_po_release_is_valid_flag
8704         FROM po_releases
8705        WHERE po_release_id = l_po_release_id
8706        /* For bug 4038403. Added by lgopalsa
8707           Need to validate the lines for matching */
8708        and nvl(authorization_status, 'INCOMPLETE') in ('APPROVED',
8709                                                        'REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
8710 
8711     EXCEPTION
8712       WHEN NO_DATA_FOUND THEN
8713          -- po release id is invalid
8714          -- set contextual information for XML GATEWAY
8715          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8716                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8717                         p_invoice_lines_rec.invoice_line_id,
8718                         'INVALID PO RELEASE NUM',
8719                         p_default_last_updated_by,
8720                         p_default_last_update_login,
8721                         current_calling_sequence) <> TRUE) THEN
8722            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8723              AP_IMPORT_UTILITIES_PKG.Print(
8724                AP_IMPORT_INVOICES_PKG.g_debug_switch,
8725                'insert_rejections<-'||current_calling_sequence);
8726            END IF;
8727            RAISE check_po_failure;
8728          END IF;
8729 
8730          l_current_invoice_status := 'N';
8731     END;
8732 
8733   END IF;
8734 
8735   ------------------------------------------------------------
8736   -- Case 8, Reject if po_release_num is invalid
8737   ------------------------------------------------------------
8738   IF ((p_invoice_lines_rec.release_num IS NOT NULL) AND
8739       (l_po_release_id IS NULL) AND
8740       (l_po_header_id IS NOT NULL)) THEN
8741     --
8742     BEGIN
8743       debug_info := '(v_check_line_po_info 8) Validate po_release_num';
8744       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8745         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8746                                       debug_info);
8747       END IF;
8748       --
8749       SELECT 'Y',
8750          po_release_id
8751         INTO l_po_release_is_valid_flag,
8752          l_po_release_id
8753         FROM po_releases
8754        WHERE release_num = p_invoice_lines_rec.release_num
8755          AND po_header_id = l_po_header_id
8756        /* For bug 4038403
8757           Need to validate the lines for matching */
8758        and nvl(authorization_status, 'INCOMPLETE') in ('APPROVED',
8759                                                        'REQUIRES REAPPROVAL','IN PROCESS');--Bug5687122 --Added In Process condition
8760 
8761     EXCEPTION
8762       WHEN NO_DATA_FOUND THEN
8763         -- po release number is invalid
8764         -- Set contextual information for XML GATEWAY
8765         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8766                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8767                         p_invoice_lines_rec.invoice_line_id,
8768                         'INVALID PO RELEASE NUM',
8769                         p_default_last_updated_by,
8770                         p_default_last_update_login,
8771                         current_calling_sequence,
8772                         'Y',
8773                         'PO RELEASE NUMBER',
8774                         p_invoice_lines_rec.release_num) <> TRUE) THEN
8775           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8776             AP_IMPORT_UTILITIES_PKG.Print(
8777             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8778             'insert_rejections<-'||current_calling_sequence);
8779           END IF;
8780           RAISE check_po_failure;
8781         END IF;
8782 
8783         l_current_invoice_status := 'N';
8784     END;
8785 
8786   END IF;
8787 
8788 
8789   ---------------------------------------------------------------------------
8790   -- Case 9, Reject if po_release_id and release_num is inconsistent
8791   ---------------------------------------------------------------------------
8792   IF ((l_po_release_id IS NOT NULL) AND
8793       (p_invoice_lines_rec.release_num IS NOT NULL)) THEN
8794     --
8795     BEGIN
8796       debug_info := '(v_check_line_po_info 9) Check inconsistence for '
8797                     ||'release_num and po_release_id';
8798       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8799         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8800                                       debug_info);
8801       END IF;
8802       --
8803       SELECT 'Y'
8804         INTO l_po_rel_is_consistent_flag
8805         FROM po_releases
8806        WHERE release_num = p_invoice_lines_rec.release_num
8807          AND po_release_id = l_po_release_id;
8808     EXCEPTION
8809       WHEN NO_DATA_FOUND THEN
8810         -- po release information is inconsistent
8811         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8812             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8813             p_invoice_lines_rec.invoice_line_id,
8814             'INCONSISTENT RELEASE INFO',
8815             p_default_last_updated_by,
8816             p_default_last_update_login,
8817             current_calling_sequence) <> TRUE) THEN
8818           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8819             AP_IMPORT_UTILITIES_PKG.Print(
8820             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8821             'insert_rejections<-'||current_calling_sequence);
8822           END IF;
8823            RAISE check_po_failure;
8824         END IF;
8825         --
8826         l_current_invoice_status := 'N';
8827     END;
8828   END IF;
8829 
8830   ---------------------------------------------------------------------------
8831   -- Case 10, Reject if po_release_id and po_line_id is inconsistent
8832   ---------------------------------------------------------------------------
8833   IF ((l_po_release_id IS NOT NULL) AND
8834       (l_po_line_id IS NOT NULL)) THEN
8835     --
8836     BEGIN
8837       debug_info := '(v_check_line_po_info 10) Check inconsistence for '
8838                     ||'po_line_id and po_release_id';
8839       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8840         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8841                                       debug_info);
8842       END IF;
8843       --
8844       SELECT 'Y'
8845         INTO l_po_rel_is_consistent_flag
8846         FROM po_line_locations
8847        WHERE po_line_id = l_po_line_id
8848          AND po_release_id = l_po_release_id
8849       /*Bug 2787396 we need to validate the shipment level for matching */
8850          AND nvl(approved_flag, 'N' ) = 'Y'
8851          AND rownum <=1;
8852     EXCEPTION
8853       WHEN NO_DATA_FOUND THEN
8854         -- po release/line is inconsistent
8855         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8856             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8857             p_invoice_lines_rec.invoice_line_id,
8858             'INCONSISTENT RELEASE INFO',
8859             p_default_last_updated_by,
8860             p_default_last_update_login,
8861             current_calling_sequence) <> TRUE) THEN
8862           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8863             AP_IMPORT_UTILITIES_PKG.Print(
8864             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8865             'insert_rejections<-'||current_calling_sequence);
8866           END IF;
8867          RAISE check_po_failure;
8868         END IF;
8869         --
8870         l_current_invoice_status := 'N';
8871     END;
8872   END IF;
8873 
8874   ---------------------------------------------------------------------------
8875   -- Case 10.1, Reject if po_release has more than 1 line no line info is given
8876   ---------------------------------------------------------------------------
8877   IF ((l_po_release_id IS NOT NULL) AND
8878       (l_po_line_id IS NULL)) THEN
8879     --
8880     BEGIN
8881       debug_info :=
8882         '(v_check_line_po_info 10.1) Check lines for po_release_id ';
8883       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8884         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8885                                       debug_info);
8886       END IF;
8887       --
8888       SELECT DISTINCT po_line_id
8889         INTO l_po_line_id
8890         FROM po_line_locations
8891        WHERE po_release_id = l_po_release_id
8892      /* For bug 4038403
8893          we should check at line location level approved flag
8894         as we can do invoicing for the line/shipment for which
8895         receipt is allowed and the document is already
8896         undergone approval. */
8897          AND approved_flag ='Y' ;
8898 
8899 
8900     EXCEPTION
8901       WHEN NO_DATA_FOUND THEN
8902         -- po release/line is inconsistent
8903         -- set contextual information for XML GATEWAY
8904         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8905                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8906                         p_invoice_lines_rec.invoice_line_id,
8907                         'INVALID PO RELEASE INFO',
8908                         p_default_last_updated_by,
8909                         p_default_last_update_login,
8910                         current_calling_sequence,
8911                         'Y',
8912                         'PO RELEASE NUMBER',
8913                         p_invoice_lines_rec.release_num,
8914                         'PO SHIPMENT NUMBER',
8915                         p_invoice_lines_rec.po_shipment_num,
8916                         'PO LINE NUMBER',
8917                         p_invoice_lines_rec.po_line_number) <> TRUE) THEN
8918           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8919             AP_IMPORT_UTILITIES_PKG.Print(
8920             AP_IMPORT_INVOICES_PKG.g_debug_switch,
8921             'insert_rejections<-'||current_calling_sequence);
8922           END IF;
8923           RAISE check_po_failure;
8924         END IF;
8925 
8926         l_current_invoice_status := 'N';
8927 
8928       WHEN TOO_MANY_ROWS THEN
8929         -- po release
8930         IF ((p_invoice_lines_rec.po_line_number IS NULL)      AND
8931             (p_invoice_lines_rec.inventory_item_id IS NULL)   AND
8932             (p_invoice_lines_rec.vendor_item_num IS NULL)     AND
8933             (p_invoice_lines_rec.item_description IS NULL)    AND
8934             (l_po_line_location_id IS NULL) AND
8935             (l_po_distribution_id IS NULL)) THEN
8936 
8937           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
8938             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
8939             p_invoice_lines_rec.invoice_line_id,
8940             'CAN MATCH TO ONLY 1 LINE',
8941             p_default_last_updated_by,
8942             p_default_last_update_login,
8943             current_calling_sequence) <> TRUE) THEN
8944             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8945               AP_IMPORT_UTILITIES_PKG.Print(
8946               AP_IMPORT_INVOICES_PKG.g_debug_switch,
8947               'insert_rejections<-'||current_calling_sequence);
8948             END IF;
8949             RAISE check_po_failure;
8950           END IF;
8951 
8952           l_current_invoice_status := 'N';
8953         END IF;
8954 
8955     END;
8956 
8957   END IF;
8958 
8959 --case 10.2 added for bug 4525041
8960  ---------------------------------------------------------------------------
8961   -- Case 10.2, Reject if release_num and po_line_number is inconsistent
8962  ---------------------------------------------------------------------------
8963   IF ((p_invoice_lines_rec.release_num IS NOT NULL) AND (p_invoice_lines_rec.po_line_number IS NOT NULL)
8964        AND (l_po_header_id is not null OR p_invoice_lines_rec.po_number is not null)) THEN
8965 
8966       BEGIN
8967       debug_info :=
8968       '(v_check_line_po_info 10.2) Check lines for po_release_id ';
8969       /* For bug 4038403
8970         Removed the 'STANDARD' from the condition  from both
8971          the queries as there is no need to validate the release
8972          details for standard PO */
8973 
8974       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
8975         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
8976                                       debug_info);
8977      End if;
8978 
8979       IF l_po_header_id IS NOT NULL THEN -- Fix for 2809177
8980         SELECT 'Y'
8981           INTO l_po_rel_is_consistent_flag
8982           FROM po_line_locations
8983           WHERE po_line_id = (
8984                 select po_line_id
8985                   from po_lines pol, po_headers poh
8986                 where poh.po_header_id = pol.po_header_id
8987                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
8988                   -- fix for bug 2809177 commented above line and wrote the below one
8989                   and poh.po_header_id = l_po_header_id
8990                   -- Commented below line as a fix for bug 2809177
8991                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
8992                   and poh.type_lookup_code in ('BLANKET', 'PLANNED') --, 'STANDARD')
8993                   and pol.po_line_id = nvl(l_po_line_id, pol.po_line_id)
8994                   and pol.line_num = p_invoice_lines_rec.po_line_number )
8995             AND po_release_id = (
8996                 select po_release_id
8997                   from po_releases por, po_headers poh
8998                 where poh.po_header_id = por.po_header_id
8999                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
9000                   -- fix for bug 2809177 commented above line and wrote the below one
9001                   and poh.po_header_id = l_po_header_id
9002                   -- Commented below line as a fix for bug 2809177
9003                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
9004                   and poh.type_lookup_code in ('BLANKET', 'PLANNED')--, 'STANDARD')
9005                   and por.po_header_id = l_po_header_id  -- Added as a fix for bug 2809177
9006                   and por.release_num = p_invoice_lines_rec.release_num )
9007             AND rownum <=1;
9008       ELSIF p_invoice_lines_rec.po_number IS NOT NULL THEN
9009         SELECT 'Y'
9010           INTO l_po_rel_is_consistent_flag
9011           FROM po_line_locations
9012           WHERE po_line_id = (
9013                 select po_line_id
9014                   from po_lines pol, po_headers poh
9015                 where poh.po_header_id = pol.po_header_id
9016                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
9017                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
9018                   -- fix for bug 2809177 commented above two lines and wrote the below one
9019                   and poh.segment1 = p_invoice_lines_rec.po_number
9020                   and poh.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
9021                   and pol.po_line_id = nvl(l_po_line_id, pol.po_line_id)
9022                   and pol.line_num = p_invoice_lines_rec.po_line_number )
9023             AND po_release_id = (
9024                 select po_release_id
9025                   from po_releases por, po_headers poh
9026                 where poh.po_header_id = por.po_header_id
9027                   -- and poh.po_header_id = nvl(l_po_header_id, poh.po_header_id)
9028                   -- and poh.segment1 = nvl(p_invoice_lines_rec.po_number, poh.segment1)
9029                   -- fix for bug 2809177 commented above two line and wrote the below one
9030                   and poh.segment1 = p_invoice_lines_rec.po_number
9031                   and poh.type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD')
9032                   and por.release_num = p_invoice_lines_rec.release_num )
9033             AND rownum <=1;
9034       END IF ;
9035 
9036       EXCEPTION
9037       WHEN NO_DATA_FOUND THEN
9038           -- po release/line is inconsistent
9039         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9040                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9041                         p_invoice_lines_rec.invoice_line_id,
9042                         'INCONSISTENT RELEASE INFO',
9043                         p_default_last_updated_by,
9044                         p_default_last_update_login,
9045                         current_calling_sequence
9046                         ) <> TRUE) THEN
9047           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9048             AP_IMPORT_UTILITIES_PKG.Print(
9049             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9050             'insert_rejections<-'||current_calling_sequence);
9051           END IF;
9052           RAISE check_po_failure;
9053 END IF;
9054       END;
9055 END IF;
9056   ------------------------------------------------------------
9057   -- Case 11, Reject if p_inventory_item_id is invalid
9058   ------------------------------------------------------------
9059   IF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
9060       (l_po_line_id IS NULL) AND
9061       (l_po_release_id IS NULL) AND
9062       (l_po_header_id IS NOT NULL)) THEN
9063     --
9064     BEGIN
9065       debug_info :=
9066         '(v_check_line_po_info 11) Validate p_inventory_item_id';
9067       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9068         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9069                                       debug_info);
9070       END IF;
9071       --
9072       SELECT 'Y', po_line_id
9073         INTO l_po_is_valid_flag, l_po_line_id
9074         FROM po_lines
9075        WHERE item_id = p_invoice_lines_rec.inventory_item_id
9076          AND po_header_id = l_po_header_id;
9077     EXCEPTION
9078       WHEN NO_DATA_FOUND THEN
9079         -- po item id is invalid
9080         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9081             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9082             p_invoice_lines_rec.invoice_line_id,
9083             'INVALID ITEM',
9084             p_default_last_updated_by,
9085             p_default_last_update_login,
9086             current_calling_sequence) <> TRUE) THEN
9087           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9088             AP_IMPORT_UTILITIES_PKG.Print(
9089             AP_IMPORT_INVOICES_PKG.g_debug_switch,
9090             'insert_rejections<-'||current_calling_sequence);
9091           END IF;
9092            RAISE check_po_failure;
9093         END IF;
9094         --
9095         l_current_invoice_status := 'N';
9096 
9097       WHEN TOO_MANY_ROWS Then
9098         IF ((l_po_line_id    IS NULL) AND
9099             (p_invoice_lines_rec.po_line_number IS NULL) AND
9100             (l_po_line_location_id IS NULL) AND
9101             (l_po_distribution_id IS NULL)) Then
9102           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9103                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9104                  p_invoice_lines_rec.invoice_line_id,
9105                 'CAN MATCH TO ONLY 1 LINE',
9106                  p_default_last_updated_by,
9107                  p_default_last_update_login,
9108                  current_calling_sequence) <> TRUE) THEN
9109             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9110               AP_IMPORT_UTILITIES_PKG.Print(
9111                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
9112                 'insert_rejections<-'||current_calling_sequence);
9113             END IF;
9114             RAISE check_po_failure;
9115           END IF;
9116 
9117           l_current_invoice_status := 'N';
9118 
9119         END IF;
9120     END;
9121   END IF;
9122 
9123   -----------------------------------------------------------------------
9124   -- Case 11.5, Reject if p_vendor_item_num is invalid -- Bug 1873251
9125   -- changed (p_po_line_id is NULL) to (l_po_line_id is NULL) Bug 2642098
9126   -----------------------------------------------------------------------
9127   IF ((p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
9128       (l_po_line_id IS NULL) AND
9129       (l_po_release_id IS NULL) AND
9130       (l_po_header_id IS NOT NULL)) THEN
9131     --
9132     BEGIN
9133       debug_info := '(v_check_line_po_info 11.5) Validate p_vendor_item_num';
9134       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9135         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9136                                       debug_info);
9137       END IF;
9138       --
9139       SELECT 'Y', po_line_id
9140         INTO l_po_is_valid_flag, l_po_line_id
9141         FROM po_lines
9142        WHERE vendor_product_num = p_invoice_lines_rec.vendor_item_num
9143          AND po_header_id = l_po_header_id;
9144     EXCEPTION
9145       WHEN NO_DATA_FOUND THEN
9146         -- po item id is invalid
9147         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9148                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9149                         p_invoice_lines_rec.invoice_line_id,
9150                         'INVALID ITEM',
9151                         p_default_last_updated_by,
9152                         p_default_last_update_login,
9153                         current_calling_sequence,
9154                         'Y',
9155                         'SUPPLIER ITEM NUMBER',
9156                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9157           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9158             AP_IMPORT_UTILITIES_PKG.Print(
9159               AP_IMPORT_INVOICES_PKG.g_debug_switch,
9160               'insert_rejections<-'||current_calling_sequence);
9161           END IF;
9162           RAISE check_po_failure;
9163         END IF;
9164 
9165         l_current_invoice_status := 'N';
9166 
9167       WHEN TOO_MANY_ROWS THEN
9168         IF ((l_po_line_id    IS NULL)         AND
9169             (p_invoice_lines_rec.po_line_number IS NULL)      AND
9170         (l_po_line_location_id IS NULL) AND
9171             (l_po_distribution_id IS NULL)) THEN
9172 
9173           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9174                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9175                  p_invoice_lines_rec.invoice_line_id,
9176                  'CAN MATCH TO ONLY 1 LINE',
9177                  p_default_last_updated_by,
9178                  p_default_last_update_login,
9179                   current_calling_sequence,
9180                  'Y',
9181                  'SUPPLIER ITEM NUMBER',
9182                  p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9183             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9184               AP_IMPORT_UTILITIES_PKG.Print(
9185                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
9186                 'insert_rejections<-'||current_calling_sequence);
9187             END IF;
9188             RAISE check_po_failure;
9189           END IF;
9190 
9191           l_current_invoice_status := 'N';
9192 
9193         END IF;
9194     END;
9195   END IF;
9196 
9197   ---------------------------------------------------------------------------
9198   -- Case 12, Reject if p_item_description is invalid
9199   -- changed (p_po_line_id is NULL) to (l_po_line_id is NULL) Bug 2642098
9200   ---------------------------------------------------------------------------
9201   IF ((p_invoice_lines_rec.item_description IS NOT NULL) AND
9202       (l_po_line_id IS NULL) AND
9203       (l_po_release_id IS NULL) AND
9204       (l_po_header_id IS NOT NULL)) THEN
9205     --
9206     BEGIN
9207       debug_info := '(v_check_line_po_info 12) Validate p_item_description';
9208       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9209         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9210                                       debug_info);
9211       END IF;
9212       --
9213       SELECT 'Y', po_line_id
9214         INTO l_po_is_valid_flag, l_po_line_id
9215         FROM po_lines
9216        WHERE item_description like p_invoice_lines_rec.item_description
9217          AND po_header_id = l_po_header_id;
9218     EXCEPTION
9219       WHEN NO_DATA_FOUND THEN
9220         -- po item id is invalid
9221         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9222             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9223             p_invoice_lines_rec.invoice_line_id,
9224             'INVALID ITEM',
9225             p_default_last_updated_by,
9226             p_default_last_update_login,
9227             current_calling_sequence) <> TRUE) THEN
9228           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9229             AP_IMPORT_UTILITIES_PKG.Print(
9230               AP_IMPORT_INVOICES_PKG.g_debug_switch,
9231               'insert_rejections<-'||current_calling_sequence);
9232           END IF;
9233            RAISE check_po_failure;
9234         END IF;
9235         l_current_invoice_status := 'N';
9236 
9237       WHEN TOO_MANY_ROWS Then
9238 
9239         IF ((l_po_line_id    IS NULL)     AND
9240         (p_invoice_lines_rec.po_line_number IS NULL)    AND
9241         (l_po_line_location_id IS NULL) AND
9242         (l_po_distribution_id IS NULL)) THEN
9243 
9244           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9245                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9246                  p_invoice_lines_rec.invoice_line_id,
9247                 'CAN MATCH TO ONLY 1 LINE',
9248                 p_default_last_updated_by,
9249                 p_default_last_update_login,
9250                 current_calling_sequence) <> TRUE) THEN
9251             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9252               AP_IMPORT_UTILITIES_PKG.Print(
9253                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
9254                 'insert_rejections<-'||current_calling_sequence);
9255             END IF;
9256             RAISE check_po_failure;
9257           END IF;
9258 
9259           l_current_invoice_status := 'N';
9260 
9261         END IF;
9262 
9263     END;
9264 
9265   END IF;
9266 
9267   ---------------------------------------------------------------------------
9268   -- Case 13, Reject if po_inventory_item_id, p_vendor_item_num
9269   --                          and po_item_description are inconsistent
9270   --
9271   --  Added consistency check for Supplier Item Number too as part of
9272   --  the effort to support Supplier Item Number in Invoice Import
9273   --                                                         bug 1873251
9274   ---------------------------------------------------------------------------
9275 
9276   IF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
9277       (p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
9278       (l_po_header_id IS NOT NULL)) THEN
9279       --
9280      BEGIN
9281       debug_info := '(v_check_line_po_info 13.1) Check inconsistency for '
9282                     ||'po_inventory_item_id and po_vendor_item_num';
9283       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9284         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9285                                       debug_info);
9286       END IF;
9287       --
9288       SELECT 'Y'
9289         INTO l_po_line_is_consistent_flag
9290         FROM po_lines
9291        WHERE item_id = p_invoice_lines_rec.inventory_item_id
9292          AND vendor_product_num = p_invoice_lines_rec.vendor_item_num
9293          AND po_header_id = l_po_header_id;
9294      EXCEPTION
9295        WHEN NO_DATA_FOUND THEN
9296         -- po line information is inconsistent
9297         -- bug 2581097 added contextual information for XML GATEWAY
9298          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9299                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9300                         p_invoice_lines_rec.invoice_line_id,
9301                         'INCONSISTENT PO LINE INFO',
9302                         p_default_last_updated_by,
9303                         p_default_last_update_login,
9304                         current_calling_sequence,
9305                         'Y',
9306                         'SUPPLIER ITEM NUMBER',
9307                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9308            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9309              AP_IMPORT_UTILITIES_PKG.Print(
9310                AP_IMPORT_INVOICES_PKG.g_debug_switch,
9311                'insert_rejections<-'||current_calling_sequence);
9312            END IF;
9313            RAISE check_po_failure;
9314          END IF;
9315 
9316          l_current_invoice_status := 'N';
9317 
9318        WHEN TOO_MANY_ROWS Then
9319 
9320               IF ((l_po_line_id    IS NULL)          AND
9321               (p_invoice_lines_rec.po_line_number IS NULL)      AND
9322               (l_po_line_location_id IS NULL) AND
9323               (l_po_distribution_id IS NULL)) THEN
9324 
9325                   -- bug 2581097 added contextual information for XML GATEWAY
9326 
9327                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9328                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9329                         p_invoice_lines_rec.invoice_line_id,
9330                         'CAN MATCH TO ONLY 1 LINE',
9331                         p_default_last_updated_by,
9332                         p_default_last_update_login,
9333                         current_calling_sequence,
9334                         'Y',
9335                         'SUPPLIER ITEM NUMBER',
9336                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9337 
9338                     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9339                 AP_IMPORT_UTILITIES_PKG.Print(
9340                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
9341                   'insert_rejections<-'||current_calling_sequence);
9342                     END IF;
9343                     RAISE check_po_failure;
9344                   END IF;
9345 
9346                 l_current_invoice_status := 'N';
9347 
9348               END IF;
9349      END;
9350 
9351   ELSIF ((p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
9352          (p_invoice_lines_rec.item_description IS NOT NULL)  AND
9353          (l_po_header_id IS NOT NULL))     THEN
9354       --
9355      BEGIN
9356       debug_info := '(v_check_line_po_info 13.2) Check inconsistency for '
9357                     ||'po_inventory_item_id and po_item_description';
9358       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9359         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9360                                       debug_info);
9361       END IF;
9362       --
9363       SELECT 'Y'
9364          INTO l_po_line_is_consistent_flag
9365         FROM po_lines
9366        WHERE item_id = p_invoice_lines_rec.inventory_item_id
9367      AND item_description like p_invoice_lines_rec.item_description
9368          AND po_header_id = l_po_header_id;
9369      EXCEPTION
9370        WHEN NO_DATA_FOUND THEN
9371          -- po line information is inconsistent
9372          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9373             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9374             p_invoice_lines_rec.invoice_line_id,
9375             'INCONSISTENT PO LINE INFO',
9376             p_default_last_updated_by,
9377             p_default_last_update_login,
9378             current_calling_sequence) <> TRUE) THEN
9379 
9380        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9381                AP_IMPORT_UTILITIES_PKG.Print(
9382                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
9383                  'insert_rejections<-'||current_calling_sequence);
9384            END IF;
9385            RAISE check_po_failure;
9386          END IF;
9387          l_current_invoice_status := 'N';
9388 
9389         WHEN TOO_MANY_ROWS Then
9390 
9391           IF ((l_po_line_id    IS NULL) AND
9392               (p_invoice_lines_rec.po_line_number IS NULL) AND
9393           (l_po_line_location_id IS NULL) AND
9394           (l_po_distribution_id IS NULL)) Then
9395 
9396              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9397                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9398                        p_invoice_lines_rec.invoice_line_id,
9399                       'CAN MATCH TO ONLY 1 LINE',
9400                        p_default_last_updated_by,
9401                        p_default_last_update_login,
9402                        current_calling_sequence) <> TRUE) THEN
9403 
9404              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9405                   AP_IMPORT_UTILITIES_PKG.Print(
9406                            AP_IMPORT_INVOICES_PKG.g_debug_switch,
9407                           'insert_rejections<-'||current_calling_sequence);
9408                 END IF;
9409           RAISE check_po_failure;
9410               END IF;
9411 
9412               l_current_invoice_status := 'N';
9413 
9414             END IF;
9415      END;
9416 
9417   END IF;
9418 
9419   ---------------------------------------------------------------------------
9420   -- Case 14, Reject if po_line_id and p_inventory_item_id are inconsistent
9421   ---------------------------------------------------------------------------
9422 
9423   IF ((l_po_line_id IS NOT NULL) AND
9424       (p_invoice_lines_rec.inventory_item_id IS NOT NULL)) THEN
9425       --
9426      BEGIN
9427        debug_info := '(v_check_line_po_info 14) Check inconsistency for '
9428                      ||'po_line_id and po_inventory_item_id';
9429        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9430          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9431                                       debug_info);
9432        END IF;
9433        --
9434        --
9435        SELECT 'Y'
9436        INTO l_po_line_is_consistent_flag
9437      FROM po_lines
9438         WHERE item_id = p_invoice_lines_rec.inventory_item_id
9439       AND po_line_id = l_po_line_id;
9440      EXCEPTION
9441        WHEN NO_DATA_FOUND THEN
9442          -- po line information is inconsistent
9443          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9444             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9445              p_invoice_lines_rec.invoice_line_id,
9446             'INCONSISTENT PO LINE INFO',
9447              p_default_last_updated_by,
9448              p_default_last_update_login,
9449              current_calling_sequence) <> TRUE) THEN
9450 
9451        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9452              AP_IMPORT_UTILITIES_PKG.Print(
9453                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
9454                 'insert_rejections<-'||current_calling_sequence);
9455            END IF;
9456            RAISE check_po_failure;
9457          END IF;
9458          --
9459          l_current_invoice_status := 'N';
9460      END;
9461 
9462   END IF;
9463 
9464   ---------------------------------------------------------------------------
9465   -- Case 15, Reject if po_line_id and p_vendor_item_num are inconsistent
9466   --      Support for Supplier Item Number     , bug 1873251
9467   ---------------------------------------------------------------------------
9468 
9469   IF ((l_po_line_id IS NOT NULL) AND
9470       (p_invoice_lines_rec.vendor_item_num IS NOT NULL)) THEN
9471       --
9472      BEGIN
9473        debug_info := '(v_check_line_po_info 15) Check inconsistency for '
9474                      ||'po_line_id and po_vendor_item_num';
9475        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9476          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9477                                       debug_info);
9478        END IF;
9479 
9480        --
9481        SELECT 'Y'
9482            INTO l_po_line_is_consistent_flag
9483          FROM po_lines
9484         WHERE vendor_product_num = p_invoice_lines_rec.vendor_item_num
9485           AND po_line_id = l_po_line_id;
9486      EXCEPTION
9487        WHEN NO_DATA_FOUND THEN
9488          -- po line information is inconsistent
9489          -- bug 2581097 added contextual information for XML GATEWAY
9490          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9491                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9492                         p_invoice_lines_rec.invoice_line_id,
9493                         'INCONSISTENT PO LINE INFO',
9494                         p_default_last_updated_by,
9495                         p_default_last_update_login,
9496                         current_calling_sequence,
9497                         'Y',
9498                         'SUPPLIER ITEM NUMBER',
9499                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9500            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9501              AP_IMPORT_UTILITIES_PKG.Print(
9502                AP_IMPORT_INVOICES_PKG.g_debug_switch,
9503               'insert_rejections<-'||current_calling_sequence);
9504            END IF;
9505            RAISE check_po_failure;
9506          END IF;
9507 
9508          l_current_invoice_status := 'N';
9509      END;
9510 
9511   END IF;
9512 
9513   ---------------------------------------------------------------------------
9514   -- Case 15.1, Reject if po_line_id and vendor_item_num are inconsistent
9515   --      Support for Supplier Item Number
9516   -- Amount Based Matching - Line should be rejected if Supplier item  No is
9517   -- supplied for service order line. However due to complex work project
9518   -- match basis will be moved at po shipment level hence all the matching
9519   -- basis related validation  will moved to shipment level.
9520   ---------------------------------------------------------------------------
9521 
9522   IF ((p_invoice_lines_rec.po_line_number IS NOT NULL) AND
9523       (p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
9524       (l_po_header_id IS NOT NULL)) THEN
9525       --
9526      BEGIN
9527        debug_info := '(v_check_line_po_info 15.1) Check inconsistency for '
9528                      ||'po_line_number and po_vendor_item_num';
9529        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9530          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9531                                       debug_info);
9532        END IF;
9533 
9534        --
9535        SELECT 'Y'
9536        INTO l_po_line_is_consistent_flag
9537        FROM po_lines pl
9538       WHERE pl.line_num = p_invoice_lines_rec.po_line_number
9539         AND vendor_product_num = p_invoice_lines_rec.vendor_item_num
9540         AND pl.po_header_id = l_po_header_id;
9541      EXCEPTION
9542        WHEN NO_DATA_FOUND THEN
9543          -- po line information is inconsistent
9544          -- bug 2581097 added contextual information for XML GATEWAY
9545          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9546                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9547                         p_invoice_lines_rec.invoice_line_id,
9548                         'INCONSISTENT PO LINE INFO',
9549                         p_default_last_updated_by,
9550                         p_default_last_update_login,
9551                         current_calling_sequence,
9552                         'Y',
9553                         'SUPPLIER ITEM NUMBER',
9554                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
9555            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9556              AP_IMPORT_UTILITIES_PKG.Print(
9557                AP_IMPORT_INVOICES_PKG.g_debug_switch,
9558               'insert_rejections<-'||current_calling_sequence);
9559            END IF;
9560            RAISE check_po_failure;
9561          END IF;
9562 
9563          l_current_invoice_status := 'N';
9564      END;
9565 
9566   END IF;
9567 
9568   ---------------------------------------------------------------------------
9569   -- Case 15.2, Reject if po_line_id and vendor_item_num are inconsistent
9570   --      Support for Supplier Item Number
9571   -- Amount Based Matching - Line should be rejected if inventory item  No is
9572   -- supplied for service order line. However due to complex work project
9573   -- match basis will be moved at po shipment level hence all the matching
9574   -- basis related validation  will moved to shipment level.
9575   ---------------------------------------------------------------------------
9576 
9577   IF ((p_invoice_lines_rec.po_line_number IS NOT NULL) AND
9578       (p_invoice_lines_rec.inventory_item_id IS NOT NULL) AND
9579       (l_po_header_id IS NOT NULL)) THEN
9580       --
9581      BEGIN
9582        debug_info := '(v_check_line_po_info 15.1) Check inconsistency for '
9583                      ||'po_line_number and inventory_item_id';
9584        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9585          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9586                                       debug_info);
9587        END IF;
9588 
9589        --
9590        SELECT 'Y'
9591        INTO l_po_line_is_consistent_flag
9592        FROM po_lines pl
9593       WHERE pl.line_num = p_invoice_lines_rec.po_line_number
9594         -- Bug 6734046 changed vendor_product_num to item_id
9595         AND pl.item_id = p_invoice_lines_rec.inventory_item_id
9596         AND pl.po_header_id = l_po_header_id;
9597      EXCEPTION
9598        WHEN NO_DATA_FOUND THEN
9599          -- po line information is inconsistent
9600          -- bug 2581097 added contextual information for XML GATEWAYi
9601          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9602             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9603              p_invoice_lines_rec.invoice_line_id,
9604             'INCONSISTENT PO LINE INFO',
9605              p_default_last_updated_by,
9606              p_default_last_update_login,
9607              current_calling_sequence) <> TRUE) THEN
9608            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9609              AP_IMPORT_UTILITIES_PKG.Print(
9610                AP_IMPORT_INVOICES_PKG.g_debug_switch,
9611               'insert_rejections<-'||current_calling_sequence);
9612            END IF;
9613            RAISE check_po_failure;
9614          END IF;
9615 
9616          l_current_invoice_status := 'N';
9617      END;
9618 
9619   END IF;
9620 
9621   -----------------------------------------------------------
9622   -- Case 16,  Reject if po_line_location_id is invalid
9623   -----------------------------------------------------------
9624 
9625   IF (l_po_line_location_id IS NOT NULL ) THEN
9626     --
9627     BEGIN
9628       debug_info := '(v_check_line_po_info 16) Validate po_line_location_id';
9629       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9630         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9631                                       debug_info);
9632       END IF;
9633       --
9634       SELECT 'Y'
9635         INTO l_po_shipment_is_valid_flag
9636         FROM po_line_locations
9637        WHERE line_location_id = l_po_line_location_id
9638        /* For bug 4038403
9639              Need to check the validation for
9640              line location approved_flag */
9641          and approved_flag ='Y';
9642 
9643     EXCEPTION
9644       WHEN NO_DATA_FOUND THEN
9645         -- po line location id is invalid
9646         -- bug 2581097 added contextual information for XML GATEWAY
9647         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9648                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9649                   p_invoice_lines_rec.invoice_line_id,
9650                  'INVALID PO SHIPMENT NUM',
9651                   p_default_last_updated_by,
9652                   p_default_last_update_login,
9653                   current_calling_sequence,
9654                  'Y',
9655                  'PO SHIPMENT NUMBER',
9656                   p_invoice_lines_rec.po_shipment_num) <> TRUE) THEN
9657           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9658             AP_IMPORT_UTILITIES_PKG.Print(
9659               AP_IMPORT_INVOICES_PKG.g_debug_switch,
9660               'insert_rejections<-'||current_calling_sequence);
9661           END IF;
9662           RAISE check_po_failure;
9663         END IF;
9664 
9665       l_current_invoice_status := 'N';
9666     END;
9667 
9668   END IF;
9669 
9670 
9671   ------------------------------------------------------------
9672   -- Case 17, Reject if po_shipment_num is invalid
9673   ------------------------------------------------------------
9674 
9675   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL) AND
9676       (l_po_line_location_id IS NULL) AND
9677       (l_po_header_id IS NOT NULL)    AND
9678       (l_po_line_id IS NOT NULL)      AND
9679       (l_po_release_id IS NULL))     THEN
9680     --
9681     BEGIN
9682       debug_info := '(v_check_line_po_info 17) Validate po_shipment_num';
9683       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9684         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9685                                       debug_info);
9686       END IF;
9687       --
9688 
9689       SELECT 'Y', line_location_id
9690          INTO l_po_shipment_is_valid_flag, l_po_line_location_id
9691         FROM po_line_locations
9692        WHERE shipment_num = p_invoice_lines_rec.po_shipment_num
9693          AND po_header_id = l_po_header_id
9694          AND po_line_id = l_po_line_id;
9695     EXCEPTION
9696       WHEN NO_DATA_FOUND THEN
9697         -- po shipment number is invalid
9698         -- bug 2581097 added contextual information for XML GATEWAY
9699         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9700                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9701                         p_invoice_lines_rec.invoice_line_id,
9702                         'INVALID PO SHIPMENT NUM',
9703                         p_default_last_updated_by,
9704                         p_default_last_update_login,
9705                         current_calling_sequence,
9706                         'Y',
9707                         'PO SHIPMENT NUMBER',
9708                         p_invoice_lines_rec.po_shipment_num) <> TRUE) THEN
9709           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9710             AP_IMPORT_UTILITIES_PKG.Print(
9711               AP_IMPORT_INVOICES_PKG.g_debug_switch,
9712               'insert_rejections<-'||current_calling_sequence);
9713           END IF;
9714           RAISE check_po_failure;
9715         END IF;
9716 
9717         l_current_invoice_status := 'N';
9718       WHEN TOO_MANY_ROWS THEN
9719         -- po release info is required
9720         -- bug 2581097 added contextual information for XML GATEWAY
9721         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9722                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9723                         p_invoice_lines_rec.invoice_line_id,
9724                         'INVALID PO RELEASE INFO',
9725                         p_default_last_updated_by,
9726                         p_default_last_update_login,
9727                         current_calling_sequence,
9728                         'Y',
9729                         'PO RELEASE NUMBER',
9730                         p_invoice_lines_rec.release_num,
9731                         'PO SHIPMENT NUMBER',
9732                         p_invoice_lines_rec.po_shipment_num,
9733                         'PO LINE NUMBER',
9734                         p_invoice_lines_rec.po_line_number ) <> TRUE) THEN
9735           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9736              AP_IMPORT_UTILITIES_PKG.Print(
9737                AP_IMPORT_INVOICES_PKG.g_debug_switch,
9738                'insert_rejections<-'||current_calling_sequence);
9739           END IF;
9740           RAISE check_po_failure;
9741         END IF;
9742         l_current_invoice_status := 'N';
9743     END;
9744 
9745   END IF;
9746 
9747 
9748   ------------------------------------------------------------
9749   -- Case 18, Reject if p_ship_to_location_code is invalid
9750   ------------------------------------------------------------
9751 
9752   IF ((p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
9753       (l_po_line_location_id IS NULL) AND
9754       (l_po_header_id IS NOT NULL) AND
9755       (l_po_line_id IS NOT NULL) AND
9756       (l_po_release_id IS NULL)) THEN
9757       --
9758     BEGIN
9759      debug_info := '(v_check_line_po_info 18) Validate p_ship_to_location_code';
9760       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9761         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9762                                       debug_info);
9763       END IF;
9764       --
9765 
9766       SELECT 'Y', line_location_id
9767          INTO l_po_shipment_is_valid_flag, l_po_line_location_id
9768         FROM po_line_locations pll,
9769              hr_locations hl
9770        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
9771          AND hl.location_id = pll.ship_to_location_id
9772           AND pll.po_header_id = l_po_header_id
9773          AND pll.po_line_id = l_po_line_id;
9774 
9775      EXCEPTION
9776        WHEN NO_DATA_FOUND THEN
9777          -- po shipment number is invalid
9778          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9779             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9780             p_invoice_lines_rec.invoice_line_id,
9781             'INVALID LOCATION CODE',
9782             p_default_last_updated_by,
9783             p_default_last_update_login,
9784             current_calling_sequence) <> TRUE) THEN
9785 
9786        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9787              AP_IMPORT_UTILITIES_PKG.Print(
9788              AP_IMPORT_INVOICES_PKG.g_debug_switch,
9789                'insert_rejections<-'||current_calling_sequence);
9790            END IF;
9791            RAISE check_po_failure;
9792          END IF;
9793          --
9794          l_current_invoice_status := 'N';
9795 
9796        WHEN TOO_MANY_ROWS THEN
9797          IF (p_invoice_lines_rec.po_shipment_num IS NULL) Then
9798            -- po shipment to Location is not unique for a Line
9799            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9800                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9801                  p_invoice_lines_rec.invoice_line_id,
9802                  'NON UNIQUE LOCATION CODE',
9803                  p_default_last_updated_by,
9804                  p_default_last_update_login,
9805                  current_calling_sequence) <> TRUE) THEN
9806 
9807          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9808                AP_IMPORT_UTILITIES_PKG.Print(
9809                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
9810                 'insert_rejections<-'||current_calling_sequence);
9811              END IF;
9812              RAISE check_po_failure;
9813              END IF;
9814            --
9815            l_current_invoice_status := 'N';
9816 
9817          END IF;
9818      END;
9819 
9820   END IF;
9821 
9822   ------------------------------------------------------------
9823   -- Case 19, Reject if po_shipment_num is invalid
9824   ------------------------------------------------------------
9825 
9826   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL) AND
9827       (l_po_line_location_id IS NULL) AND
9828       (l_po_header_id IS NOT NULL)    AND
9829       (l_po_release_id IS NOT NULL)) THEN
9830     --
9831     BEGIN
9832       debug_info := '(v_check_line_po_info 19) Validate po_shipment_num';
9833       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9834         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9835                                       debug_info);
9836       END IF;
9837       --
9838       SELECT 'Y', line_location_id,
9839       	     po_line_id
9840         INTO l_po_shipment_is_valid_flag, l_po_line_location_id,
9841   	     l_po_line_id
9842         FROM po_line_locations
9843        WHERE shipment_num = p_invoice_lines_rec.po_shipment_num
9844          AND po_header_id = l_po_header_id
9845          AND po_release_id = l_po_release_id;
9846     EXCEPTION
9847       WHEN NO_DATA_FOUND THEN
9848         -- po shipment number is invalid
9849         -- bug 2581097 added contextual information for XML GATEWAY
9850         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9851                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9852                         p_invoice_lines_rec.invoice_line_id,
9853                         'INVALID PO SHIPMENT NUM',
9854                         p_default_last_updated_by,
9855                         p_default_last_update_login,
9856                         current_calling_sequence,
9857                         'Y',
9858                         'PO SHIPMENT NUMBER',
9859                         p_invoice_lines_rec.po_shipment_num) <> TRUE) THEN
9860           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9861                AP_IMPORT_UTILITIES_PKG.Print(
9862                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
9863                 'insert_rejections<-'||current_calling_sequence);
9864           END IF;
9865           RAISE check_po_failure;
9866         END IF;
9867 
9868         l_current_invoice_status := 'N';
9869     END;
9870 
9871   END IF;
9872 
9873 
9874   ------------------------------------------------------------
9875   -- Case 20, Reject if p_ship_to_location_code is invalid
9876   ------------------------------------------------------------
9877 
9878   IF ((p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
9879       (l_po_line_location_id IS NULL) AND
9880       (l_po_header_id IS NOT NULL) AND
9881       (l_po_release_id IS NOT NULL)) THEN
9882       --
9883     BEGIN
9884       debug_info :=
9885         '(v_check_line_po_info 20) Validate p_ship_to_location_code';
9886       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9887         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9888                                       debug_info);
9889       END IF;
9890       --
9891       SELECT 'Y', line_location_id,
9892              po_line_id
9893         INTO l_po_shipment_is_valid_flag, l_po_line_location_id,
9894 	     l_po_line_id
9895         FROM po_line_locations pll, hr_locations hl
9896        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
9897          AND hl.location_id = pll.ship_to_location_id
9898           AND pll.po_header_id = l_po_header_id
9899          AND pll.po_release_id = l_po_release_id;
9900 
9901     EXCEPTION
9902       WHEN NO_DATA_FOUND THEN
9903         -- po shipment number is invalid
9904         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9905            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9906             p_invoice_lines_rec.invoice_line_id,
9907             'INVALID LOCATION CODE',
9908             p_default_last_updated_by,
9909             p_default_last_update_login,
9910             current_calling_sequence) <> TRUE) THEN
9911 
9912           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9913                AP_IMPORT_UTILITIES_PKG.Print(
9914                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
9915                 'insert_rejections<-'||current_calling_sequence);
9916           END IF;
9917           RAISE check_po_failure;
9918         END IF;
9919         --
9920         l_current_invoice_status := 'N';
9921   -- CHANGES FOR BUG - 2772949  ** STARTS **
9922 	WHEN TOO_MANY_ROWS THEN
9923 		NULL;
9924   -- CHANGES FOR BUG - 2772949  ** ENDS   **
9925   END;
9926   END IF;
9927 
9928   ---------------------------------------------------------------------------
9929   -- Case 21, Reject if po_line_location_id and po_shipment_num is inconsistent
9930   ---------------------------------------------------------------------------
9931 
9932   IF ((l_po_line_location_id IS NOT NULL) AND
9933       (p_invoice_lines_rec.po_shipment_num IS NOT NULL))    THEN
9934       --
9935     BEGIN
9936       debug_info := '(v_check_line_po_info 21) Check inconsistence for '
9937                     ||'po_shipment_num and po_line_location_id';
9938       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9939         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9940                                       debug_info);
9941       END IF;
9942       --
9943       SELECT 'Y'
9944       INTO l_po_shipment_is_consis_flag
9945     FROM po_line_locations
9946        WHERE shipment_num = p_invoice_lines_rec.po_shipment_num
9947      AND line_location_id = l_po_line_location_id;
9948     EXCEPTION
9949       WHEN NO_DATA_FOUND THEN
9950         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9951             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9952             p_invoice_lines_rec.invoice_line_id,
9953             'INCONSISTENT PO SHIPMENT',
9954             p_default_last_updated_by,
9955             p_default_last_update_login,
9956             current_calling_sequence) <> TRUE) THEN
9957           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9958                AP_IMPORT_UTILITIES_PKG.Print(
9959                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
9960                 'insert_rejections<-'||current_calling_sequence);
9961           END IF;
9962           RAISE check_po_failure;
9963         END IF;
9964         --
9965         l_current_invoice_status := 'N';
9966     END;
9967 
9968   END IF;
9969 
9970   ---------------------------------------------------------------------------
9971   -- Case 22, Reject if po_line_location_id and p_ship_to_location_code is
9972   -- inconsistent
9973   ---------------------------------------------------------------------------
9974   IF ((l_po_line_location_id IS NOT NULL) AND
9975       (p_invoice_lines_rec.ship_to_location_code IS NOT NULL)) THEN
9976     --
9977     BEGIN
9978       debug_info := '(v_check_line_po_info 22) Check inconsistence for '
9979                     ||'p_ship_to_location_code and po_line_location_id';
9980       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
9981         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
9982                                       debug_info);
9983       END IF;
9984       --
9985 
9986       SELECT 'Y'
9987           INTO l_po_shipment_is_consis_flag
9988         FROM po_line_locations pll,
9989              hr_locations hl
9990        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
9991          AND hl.location_id = pll.ship_to_location_id
9992          AND line_location_id = l_po_line_location_id;
9993 
9994     EXCEPTION
9995       WHEN NO_DATA_FOUND THEN
9996         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
9997             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
9998             p_invoice_lines_rec.invoice_line_id,
9999             'INCONSISTENT PO SHIPMENT',
10000             p_default_last_updated_by,
10001             p_default_last_update_login,
10002             current_calling_sequence) <> TRUE) THEN
10003           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10004                AP_IMPORT_UTILITIES_PKG.Print(
10005                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10006                 'insert_rejections<-'||current_calling_sequence);
10007           END IF;
10008           RAISE check_po_failure;
10009         END IF;
10010         --
10011         l_current_invoice_status := 'N';
10012     END;
10013 
10014   END IF;
10015 
10016   ---------------------------------------------------------------------------
10017   -- Case 23, Reject if p_po_shipment_num and p_ship_to_location_code is
10018   -- inconsistent
10019   ---------------------------------------------------------------------------
10020   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL)       AND
10021       (p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
10022       (l_po_header_id IS NOT NULL)                            AND
10023       (l_po_line_id IS NOT NULL)                              AND
10024       (l_po_release_id IS NULL))                             THEN
10025     --
10026     BEGIN
10027       debug_info := '(v_check_line_po_info 23) Check inconsistence for '
10028                     ||'p_ship_to_location_code and p_po_shipment_num';
10029       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10030         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10031                                       debug_info);
10032       END IF;
10033       --
10034       SELECT 'Y'
10035         INTO l_po_shipment_is_consis_flag
10036         FROM po_line_locations pll,
10037              hr_locations hl
10038        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
10039          AND hl.location_id = pll.ship_to_location_id
10040          AND po_line_id = l_po_line_id
10041          AND shipment_num = p_invoice_lines_rec.po_shipment_num
10042          AND po_header_id = l_po_header_id;
10043 
10044     EXCEPTION
10045       WHEN NO_DATA_FOUND THEN
10046         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10047             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10048                p_invoice_lines_rec.invoice_line_id,
10049             'INCONSISTENT PO SHIPMENT',
10050             p_default_last_updated_by,
10051             p_default_last_update_login,
10052             current_calling_sequence) <> TRUE) THEN
10053           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10054                AP_IMPORT_UTILITIES_PKG.Print(
10055                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10056                 'insert_rejections<-'||current_calling_sequence);
10057           END IF;
10058           --
10059           RAISE check_po_failure;
10060           --
10061         END IF;
10062         --
10063         l_current_invoice_status := 'N';
10064     END;
10065     --
10066   END IF;
10067 
10068 
10069 
10070 /* Bug 4121338*/
10071   ----------------------------------------------------------
10072   -- Case 23.1, Reject if accrue on receipt is on but
10073   -- overlay gl account is provided in line
10074 
10075   ----------------------------------------------------------
10076 
10077  IF (p_invoice_lines_rec.dist_code_combination_id IS NOT NULL OR
10078           p_invoice_lines_rec.dist_code_concatenated IS NOT NULL OR
10079               p_invoice_lines_rec.balancing_segment IS NOT NULL OR
10080               p_invoice_lines_rec.account_segment IS NOT NULL OR
10081               p_invoice_lines_rec.cost_center_segment IS NOT NULL) THEN
10082 
10083     IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL or p_invoice_lines_rec.po_line_location_id IS NOT NULL) AND
10084       (l_po_header_id IS NOT NULL) AND
10085       ((l_po_line_id IS NOT NULL AND l_po_release_id IS NULL) OR
10086        (l_po_release_id IS NOT NULL AND l_po_line_id IS NULL) OR
10087        (l_po_line_id IS NOT NULL AND l_po_release_id IS NOT NULL))) THEN /* Bug 4254606 */
10088       BEGIN
10089 
10090 
10091 
10092         debug_info := '(v_check_line_po_info 23.1) Validate po_shipment_num';
10093         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10094         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10095                                 debug_info);
10096         END IF;
10097         --
10098         --
10099 
10100         SELECT NVL(accrue_on_receipt_flag, 'N')
10101         INTO l_accrue_on_receipt_flag
10102         FROM po_line_locations
10103         WHERE ((shipment_num = p_invoice_lines_rec.po_shipment_num
10104                 AND p_invoice_lines_rec.po_shipment_num IS NOT NULL
10105                 AND p_invoice_lines_rec.po_line_location_id IS NULL)
10106              OR (line_location_id = p_invoice_lines_rec.po_line_location_id
10107                 AND p_invoice_lines_rec.po_line_location_id IS NOT NULL
10108                 AND p_invoice_lines_rec.po_shipment_num IS NULL)
10109              OR (p_invoice_lines_rec.po_shipment_num IS NOT NULL
10110                 AND p_invoice_lines_rec.po_line_location_id IS NOT NULL
10111                 AND shipment_num = p_invoice_lines_rec.po_shipment_num
10112                 AND  line_location_id = p_invoice_lines_rec.po_line_location_id))
10113         AND po_header_id = l_po_header_id
10114         AND ((po_release_id = l_po_release_id
10115  AND l_po_line_id IS NULL)
10116             OR (po_line_id = l_po_line_id
10117              AND l_po_release_id IS NULL)
10118             OR (po_line_id = l_po_line_id  /* Bug 4254606 */
10119              AND po_release_id = l_po_release_id));
10120       EXCEPTION
10121         WHEN OTHERS THEN
10122           Null;
10123       END;
10124 
10125       IF l_accrue_on_receipt_flag = 'Y' THEN
10126 
10127  	IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10128                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10129                 p_invoice_lines_rec.invoice_line_id,
10130                 'ACCRUE ON RECEIPT',  -- Bug 5235675
10131                 p_default_last_updated_by,
10132                 p_default_last_update_login,
10133                 current_calling_sequence) <> TRUE) THEN
10134             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10135                 AP_IMPORT_UTILITIES_PKG.Print(
10136                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
10137                   'insert_rejections<-'||current_calling_sequence);
10138             END IF;
10139              RAISE check_po_failure;
10140           END IF;
10141 
10142 
10143         l_current_invoice_status := 'N';
10144 
10145       END IF;
10146 
10147     END IF;
10148 
10149   END IF;
10150 
10151   /* End Bug 4121338 */
10152 
10153 
10154 
10155   ---------------------------------------------------------------------------
10156   -- Case 23, Reject if p_po_shipment_num and p_ship_to_location_code is
10157   -- inconsistent
10158   ---------------------------------------------------------------------------
10159   IF ((p_invoice_lines_rec.po_shipment_num IS NOT NULL) AND
10160       (p_invoice_lines_rec.ship_to_location_code IS NOT NULL) AND
10161       (l_po_header_id IS NOT NULL) AND
10162       (l_po_release_id IS  NOT NULL)) THEN
10163     --
10164     BEGIN
10165       debug_info := '(v_check_line_po_info 23) Check inconsistence for '
10166                      ||'p_ship_to_location_code and p_po_shipment_num';
10167       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10168         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10169                                       debug_info);
10170       END IF;
10171       --
10172       SELECT 'Y'
10173     INTO l_po_shipment_is_consis_flag
10174         FROM po_line_locations pll,
10175              hr_locations hl
10176        WHERE hl.location_code = p_invoice_lines_rec.ship_to_location_code
10177          AND hl.location_id = pll.ship_to_location_id
10178          AND po_release_id = l_po_release_id
10179          AND shipment_num = p_invoice_lines_rec.po_shipment_num
10180          AND po_header_id = l_po_header_id;
10181 
10182     EXCEPTION
10183       WHEN NO_DATA_FOUND THEN
10184         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10185             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10186             p_invoice_lines_rec.invoice_line_id,
10187             'INCONSISTENT PO SHIPMENT',
10188             p_default_last_updated_by,
10189             p_default_last_update_login,
10190             current_calling_sequence) <> TRUE) THEN
10191       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10192                AP_IMPORT_UTILITIES_PKG.Print(
10193                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10194                 'insert_rejections<-'||current_calling_sequence);
10195           END IF;
10196           RAISE check_po_failure;
10197         END IF;
10198         --
10199         l_current_invoice_status := 'N';
10200       END;
10201 
10202   END IF;
10203 
10204 
10205   -----------------------------------------------------------
10206   -- Case 25,  Reject if invalid p_po_distribution_id
10207   -----------------------------------------------------------
10208 
10209   IF (l_po_distribution_id IS NOT NULL ) THEN
10210      --
10211      BEGIN
10212       debug_info := '(v_check_line_po_info 25) Validate p_po_distribution_id';
10213       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10214         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10215                                       debug_info);
10216       END IF;
10217       --
10218       SELECT 'Y'
10219         INTO l_po_dist_is_valid_flag
10220         FROM po_distributions
10221        WHERE po_distribution_id = l_po_distribution_id
10222          AND line_location_id IS NOT NULL; /* BUG 3253594 */
10223      EXCEPTION
10224        WHEN NO_DATA_FOUND THEN
10225          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10226             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10227             p_invoice_lines_rec.invoice_line_id,
10228             'INVALID PO DIST NUM',
10229             p_default_last_updated_by,
10230             p_default_last_update_login,
10231             current_calling_sequence) <> TRUE) THEN
10232        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10233                AP_IMPORT_UTILITIES_PKG.Print(
10234                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10235                 'insert_rejections<-'||current_calling_sequence);
10236            END IF;
10237             RAISE check_po_failure;
10238          END IF;
10239          --
10240          l_current_invoice_status := 'N';
10241      END;
10242 
10243   END IF;
10244 
10245   -----------------------------------------------------------
10246   -- Case 26,  Reject if it is invalid p_po_distribution_num
10247   -----------------------------------------------------------
10248 
10249   IF ((l_po_distribution_id IS NULL) and
10250       (p_invoice_lines_rec.po_distribution_num IS NOT NULL) and
10251       (l_po_line_location_id IS NOT NULL) and
10252       (l_po_line_id IS NOT NULL) and
10253       (l_po_release_id IS NULL) and
10254       (l_po_header_id IS NOT NULL)) THEN
10255     --
10256     BEGIN
10257       debug_info := '(v_check_line_po_info 26) Validate p_po_distribution_num';
10258       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10259         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10260                                       debug_info);
10261       END IF;
10262       --
10263       SELECT 'Y' , po_distribution_id
10264       INTO l_po_dist_is_valid_flag,
10265              l_po_distribution_id
10266         FROM po_distributions
10267        WHERE distribution_num = p_invoice_lines_rec.po_distribution_num
10268          AND po_line_id = l_po_line_id
10269      AND line_location_id = l_po_line_location_id
10270          AND po_header_id = l_po_header_id;
10271 
10272     EXCEPTION
10273       WHEN NO_DATA_FOUND THEN
10274         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10275             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10276             p_invoice_lines_rec.invoice_line_id,
10277             'INVALID PO DIST NUM',
10278             p_default_last_updated_by,
10279             p_default_last_update_login,
10280             current_calling_sequence) <> TRUE) THEN
10281 
10282           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10283                AP_IMPORT_UTILITIES_PKG.Print(
10284                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10285                 'insert_rejections<-'||current_calling_sequence);
10286           END IF;
10287           RAISE check_po_failure;
10288         END IF;
10289         --
10290         l_current_invoice_status := 'N';
10291     END;
10292 
10293   END IF;
10294 
10295   ----------------------------------------------------------------------------
10296   -- Case 27,  Reject if  is invalid p_po_distribution_num
10297   ----------------------------------------------------------------------------
10298   IF ((l_po_distribution_id IS NULL) and
10299       (p_invoice_lines_rec.po_distribution_num IS NOT NULL) and
10300       (l_po_release_id IS NOT NULL) and
10301       (l_po_line_location_id IS NOT NULL) and
10302       (l_po_header_id IS NOT NULL)) THEN
10303     --
10304     BEGIN
10305       debug_info := '(v_check_line_po_info 27) Validate p_po_distribution_num';
10306       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10307         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10308                                       debug_info);
10309       END IF;
10310       --
10311       SELECT 'Y' , po_distribution_id
10312         INTO l_po_dist_is_valid_flag, l_po_distribution_id
10313         FROM po_distributions
10314        WHERE distribution_num = p_invoice_lines_rec.po_distribution_num
10315      AND po_release_id = l_po_release_id
10316      AND line_location_id = l_po_line_location_id
10317      AND po_header_id = l_po_header_id;
10318 
10319     EXCEPTION
10320       WHEN NO_DATA_FOUND THEN
10321         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10322             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10323             p_invoice_lines_rec.invoice_line_id,
10324             'INVALID PO DIST NUM',
10325             p_default_last_updated_by,
10326             p_default_last_update_login,
10327             current_calling_sequence) <> TRUE) THEN
10328 
10329       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10330                AP_IMPORT_UTILITIES_PKG.Print(
10331                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10332                 'insert_rejections<-'||current_calling_sequence);
10333           END IF;
10334           RAISE check_po_failure;
10335         END IF;
10336         --
10337         l_current_invoice_status := 'N';
10338     END;
10339 
10340   END IF;
10341 
10342   ---------------------------------------------------------------------------
10343   -- Case 28, Reject if p_po_distribution_num and p_po_distribution_id is
10344   -- inconsistent
10345   ---------------------------------------------------------------------------
10346 
10347   IF ((p_invoice_lines_rec.po_distribution_num IS NOT NULL) AND
10348       (l_po_distribution_id IS NOT NULL)) THEN
10349       --
10350      BEGIN
10351       debug_info := '(v_check_line_po_info 28) Check inconsistence for '
10352                     ||'p_po_distribution_num and p_po_distribution_id';
10353       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10354         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10355                                       debug_info);
10356       END IF;
10357       --
10358       SELECT 'Y'
10359         INTO l_po_dist_is_consistent_flag
10360         FROM po_distributions
10361        WHERE po_distribution_id = l_po_distribution_id
10362          AND distribution_num = p_invoice_lines_rec.po_distribution_num
10363          AND line_location_id IS NOT NULL; /* BUG 3253594 */
10364      EXCEPTION
10365        WHEN NO_DATA_FOUND THEN
10366          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10367             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10368             p_invoice_lines_rec.invoice_line_id,
10369             'INCONSISTENT PO DIST INFO',
10370             p_default_last_updated_by,
10371             p_default_last_update_login,
10372             current_calling_sequence) <> TRUE) THEN
10373 
10374        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10375                AP_IMPORT_UTILITIES_PKG.Print(
10376                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
10377                 'insert_rejections<-'||current_calling_sequence);
10378            END IF;
10379            RAISE check_po_failure;
10380          END IF;
10381          --
10382          l_current_invoice_status := 'N';
10383      END;
10384 
10385   END IF;
10386 
10387   --------------------------------------------
10388   -- Get Valid PO Info only if PO information
10389   -- was not rejected so far
10390   --------------------------------------------
10391   IF (l_current_invoice_status = 'Y') Then
10392 
10393     IF (l_po_number IS NULL) THEN
10394 
10395     ------------------------------------------------------------------------
10396     -- PO step 29,Get po number if it's null
10397     ------------------------------------------------------------------------
10398       ------------------------------------------------
10399       -- Case 1, if po_number is null, then we should try to
10400       -- get it from po_header_id first.  Note that po_header_id
10401       -- would be based on po_number from invoice level if po_number
10402       -- was given at invoice header and line information did not
10403       -- contain either po_header_id or po_number
10404       ------------------------------------------------
10405 
10406       IF (l_po_header_id IS NOT NULL) THEN
10407 
10408         BEGIN
10409           debug_info := '(v_check_line_po_info 29.1) Get po number from '
10410                           ||'po_header_id';
10411           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10412             AP_IMPORT_UTILITIES_PKG.Print(
10413               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10414           END IF;
10415 
10416           SELECT segment1
10417             INTO l_po_number
10418             FROM po_headers
10419            WHERE po_header_id = l_po_header_id
10420              AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
10421         EXCEPTION
10422       WHEN NO_DATA_FOUND THEN
10423         NULL;
10424         END;
10425 
10426       END IF; -- Step 29 - Case 1: l_po_header_id is not null
10427 
10428       ----------------------------------------------------
10429       -- Case 2, If l_po_number is still null, get both po_number
10430       --         and po_header_id from l_po_line_id if po_release_id
10431       --         is not available.
10432       ----------------------------------------------------
10433       IF (l_po_number is null) THEN
10434 
10435         IF ((l_po_line_id IS NOT NULL) and (l_po_release_id IS NULL)) THEN
10436 
10437           BEGIN
10438             debug_info :=
10439               '(v_check_line_po_info 29.2) Get po number from po_line_id';
10440             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10441               AP_IMPORT_UTILITIES_PKG.Print(
10442                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10443             END IF;
10444 
10445             SELECT pl.po_header_id,
10446                ph.segment1
10447           INTO l_po_header_id,
10448                l_po_number
10449            FROM po_headers ph,
10450                    po_lines pl
10451              WHERE pl.po_line_id = l_po_line_id
10452                AND pl.po_header_id = ph.po_header_id;
10453 
10454           EXCEPTION
10455         WHEN NO_DATA_FOUND THEN
10456           NULL;
10457       END;
10458 
10459       ----------------------------------------------------
10460       -- Case 3, If l_po_number is still null and po_release_id
10461       --         is not null, get both po_number
10462       --         and po_header_id from l_po_release_id
10463       ----------------------------------------------------
10464 
10465         ELSIF (l_po_release_id IS NOT NULL) Then
10466 
10467           BEGIN
10468             debug_info := '(v_check_line_po_info 29.3) Get po number from'
10469                           ||' po_release_id';
10470             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10471               AP_IMPORT_UTILITIES_PKG.Print(
10472                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10473             END IF;
10474 
10475         SELECT pr.po_header_id,
10476                ph.segment1
10477           INTO l_po_header_id,
10478                l_po_number
10479            FROM po_headers ph,
10480                po_releases pr
10481              WHERE pr.po_release_id = l_po_release_id
10482                AND pr.po_header_id = ph.po_header_id;
10483           EXCEPTION
10484         WHEN NO_DATA_FOUND THEN
10485           NULL;
10486           END;
10487 
10488         END IF; -- l_po_release_id is null and po_line_id is not null
10489 
10490       END IF; -- Step 29 - Case 2 and 3: l_po_number is null
10491 
10492       ----------------------------------------------------
10493       -- Case 4, If l_po_number is still null, get both po_number
10494       --         and po_header_id from l_po_line_location_id
10495       ----------------------------------------------------
10496       IF (l_po_number is null) THEN
10497         IF (l_po_line_location_id IS NOT NULL) THEN
10498           --
10499           -- get po_header_id and po_number from po_line_location_id
10500           --
10501           BEGIN
10502 
10503             debug_info := '(v_check_line_po_info 29.4) Get po number from '
10504                           ||'po_line_location_id';
10505             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10506               AP_IMPORT_UTILITIES_PKG.Print(
10507                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10508             END IF;
10509 
10510         SELECT pll.po_header_id,
10511                ph.segment1
10512           INTO l_po_header_id,
10513                l_po_number
10514            FROM po_headers ph,
10515                po_line_locations pll
10516              WHERE pll.line_location_id = l_po_line_location_id
10517                AND pll.po_header_id = ph.po_header_id;
10518           EXCEPTION
10519             WHEN NO_DATA_FOUND THEN
10520           NULL;
10521           END;
10522 
10523         END IF; -- l_po_line_location_id is not null
10524       END IF; -- Step 29 - Case 4: l_po_number is null
10525 
10526       ----------------------------------------------------
10527       -- Case 5, If l_po_number is still null, get both
10528       --         po_number and po_header_id from
10529       --           po_distribution_id
10530       ----------------------------------------------------
10531       IF (l_po_number is null) THEN
10532         IF (l_po_distribution_id IS NOT NULL) THEN
10533           --
10534           -- get po_header_id and po_number from po_distribution_id
10535           --
10536           BEGIN
10537 
10538             debug_info := '(v_check_line_po_info 29.5) Get po number from '
10539                           ||'po_distribution_id';
10540             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10541               AP_IMPORT_UTILITIES_PKG.Print(
10542                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10543             END IF;
10544 
10545             SELECT pd.po_header_id,
10546                ph.segment1
10547           INTO l_po_header_id,
10548                l_po_number
10549            FROM po_headers ph,
10550                po_distributions pd
10551              WHERE pd.po_distribution_id = l_po_distribution_id
10552                AND pd.po_header_id = ph.po_header_id
10553                AND pd.line_location_id IS NOT NULL; /* BUG 3253594 */
10554           EXCEPTION
10555         WHEN NO_DATA_FOUND THEN
10556           NULL;
10557       END;
10558 
10559         END IF; -- l_po_distribution_id is not NULL
10560       END IF; -- Step 29 - Case 5: l_po_number is null
10561 
10562     END IF;  -- (PO step 29) -- l_po_number is null
10563 
10564     -----------------------------------------------------------------------
10565     -- Step 30
10566     -- Get po_header_id from po_number if still null
10567     -----------------------------------------------------------------------
10568     IF ((l_po_number IS NOT NULL) AND
10569         (l_po_header_id IS NULL)) THEN
10570 
10571       debug_info :=
10572           '(v_check_line_po_info 30) Get po_header_id from po_number';
10573       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10574         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10575                                       debug_info);
10576       END IF;
10577       --bug2268553 to differentiate PO from RFQ and Quotation
10578       SELECT po_header_id
10579         INTO l_po_header_id
10580         FROM po_headers
10581        WHERE segment1 = l_po_number
10582          AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
10583 
10584     END IF; -- Step 30: po_number is not null but po_header_id is null
10585 
10586     -- Get other po infomation
10587     -- only if l_po_header_id is not null
10588     --
10589 
10590     IF (l_po_header_id IS NOT NULL) THEN
10591       ------------------------------------------------------------------------
10592       -- Step 31
10593       -- Get po_line_id
10594       ------------------------------------------------------------------------
10595       debug_info := '(v_check_line_po_info 31) Get po_line_id';
10596       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10597          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10598                                       debug_info);
10599       END IF;
10600 
10601       -------------------------------------------------------
10602       -- Case 1, If po_line_id is still null, get it from
10603       --  l_po_line_location_id if po_line_location_id is not null
10604       --------------------------------------------------------
10605       IF (l_po_line_id IS NULL) THEN
10606         IF (l_po_line_location_id IS NOT NULL) THEN
10607 
10608       BEGIN
10609 
10610             debug_info := '(v_check_line_po_info 31.1) Get po_line_id from '
10611                           ||'po_line_location_id';
10612             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10613               AP_IMPORT_UTILITIES_PKG.Print(
10614                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10615             END IF;
10616 
10617         SELECT po_line_id
10618           INTO l_po_line_id
10619           FROM po_line_locations
10620           WHERE line_location_id = l_po_line_location_id;
10621       EXCEPTION
10622         WHEN NO_DATA_FOUND THEN
10623               NULL;
10624       END;
10625 
10626         END IF; --  l_po_line_location_id is not null
10627       END IF; -- Step 31 - Case 1: l_po_line_id is null
10628 
10629       -------------------------------------------------------
10630       -- Case 2, If l_po_line_id is still null, get it from
10631       --  po_distribution_id if po_distribution_id is not null
10632       --------------------------------------------------------
10633       IF (l_po_line_id IS NULL) THEN
10634       IF (l_po_distribution_id IS NOT NULL) THEN
10635 
10636       BEGIN
10637 
10638             debug_info := '(v_check_line_po_info 31.2) Get po_line_id from '
10639                           ||'po_distribution_id';
10640             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10641               AP_IMPORT_UTILITIES_PKG.Print(
10642                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10643             END IF;
10644 
10645         SELECT po_line_id
10646           INTO l_po_line_id
10647           FROM po_distributions
10648           WHERE po_distribution_id = l_po_distribution_id
10649             AND line_location_id IS NOT NULL; /* BUG 3253594 */
10650       EXCEPTION
10651         WHEN NO_DATA_FOUND THEN
10652               NULL;
10653       END;
10654 
10655     END IF; -- l_po_distribution_id is not null
10656 
10657    END IF; -- Step 31 - Case 2: l_po_line_id is null
10658 
10659       -------------------------------------------------------
10660       -- Case 3, If po_line_id is still null, default to
10661       -- the first line (it should be one line)
10662       -- If more than 1 line then reject NO PO LINE NUM
10663       --------------------------------------------------------
10664    IF (l_po_line_id IS NULL) THEN
10665 
10666         BEGIN
10667 
10668           debug_info := '(v_check_line_po_info 31.3) Default po_line_id from '
10669                         ||'the first line, if only one line';
10670           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10671             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10672                                        debug_info);
10673           END IF;
10674 
10675           SELECT po_line_id
10676             INTO l_po_line_id
10677             FROM po_lines
10678            WHERE po_header_id = l_po_header_id;
10679 
10680         EXCEPTION
10681           WHEN NO_DATA_FOUND Then
10682             NULL;
10683 
10684           WHEN TOO_MANY_ROWS Then
10685             debug_info := '(v_check_line_po_info 31.4) Too many po lines';
10686             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10687               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10688                                       debug_info);
10689             END IF;
10690 
10691             -- bug 2581097 added contextual information for XML GATEWAY
10692 
10693             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10694                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10695                         p_invoice_lines_rec.invoice_line_id,
10696                         'NO PO LINE NUM',
10697                         p_default_last_updated_by,
10698                         p_default_last_update_login,
10699                         current_calling_sequence,
10700                         'Y',
10701                         'PO NUMBER',
10702                         l_po_number) <> TRUE) THEN
10703               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10704                 AP_IMPORT_UTILITIES_PKG.Print(
10705                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
10706                     'insert_rejections<-'||current_calling_sequence);
10707               END IF;
10708               RAISE check_po_failure;
10709             END IF;
10710             --
10711             l_current_invoice_status := 'N';
10712             --
10713         END;
10714 
10715       END IF; -- Step 31 - Case 3: l_po_line_id is null
10716 
10717     END IF; -- Step 31: (l_po_header_id IS NOT NULL - get po_line_id if null)
10718 
10719     -- Bug # 1042447
10720     --
10721     -- Get  po shipment infomation
10722     -- only if p_po_header_id is not null and po_line_id is not null
10723 
10724     IF (l_po_header_id IS NOT NULL) AND (l_po_line_id is not NULL) THEN
10725       -----------------------------------------------------------------------
10726       -- Step 32
10727       -- Get Get po_line_location_id
10728       -----------------------------------------------------------------------
10729       debug_info := '(v_check_line_po_info 32) Get po_line_location_id';
10730       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10731         AP_IMPORT_UTILITIES_PKG.Print(
10732           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10733       END IF;
10734 
10735       -------------------------------------------------------
10736       -- Case 1, If l_po_line_location_id id still null, get it from
10737       --  po_distribution_id
10738       --------------------------------------------------------
10739       IF (l_po_line_location_id IS NULL) THEN
10740         IF (l_po_distribution_id IS NOT NULL) THEN
10741 
10742           BEGIN
10743             --
10744             debug_info := '(v_check_line_po_info 32.1) Get po_line_id from '
10745                            ||'po_distribution_id';
10746             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10747               AP_IMPORT_UTILITIES_PKG.Print(
10748                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10749             END IF;
10750 
10751             SELECT line_location_id
10752               INTO l_po_line_location_id
10753               FROM po_distributions
10754               WHERE po_distribution_id = l_po_distribution_id
10755                 AND line_location_id IS NOT NULL; /* BUG 3253594 */
10756           EXCEPTION
10757             WHEN NO_DATA_FOUND THEN
10758                   NULL;
10759           END;
10760           --
10761         END IF; -- l_po_distribution_id is not null
10762       END IF; -- l_po_line_location_id is null
10763 
10764       -------------------------------------------------------
10765       -- Case 2, If po_line_location_id id still null, default to
10766       -- the first line (it should be one one line)
10767       -- If more than 1 line then reject NO SHIPMENT LINE NUM
10768       --------------------------------------------------------
10769       IF (l_po_line_location_id IS NULL) THEN
10770 
10771         BEGIN
10772 
10773           debug_info := '(v_check_line_po_info 32.2) Default '
10774                          ||'po_line_location_id from the first line, '
10775                          ||'if only one line';
10776           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10777             AP_IMPORT_UTILITIES_PKG.Print(
10778                AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10779           END IF;
10780 
10781 	  /*--------------------------------------------------------------------+
10782 	  | --Contract Payments:						|
10783 	  | 1.For the case of complex works purchase order, if it is a		|
10784 	  |   A)Prepayment Invoice,we should not reject if we can derive        |
10785 	  |     a single shipment of type 'Prepayment' from the PO line		|
10786 	  |    we should not reject it.						|
10787           |   B)Any other invoice (Std, credit,debit, mixed), we should		|
10788 	  |    not reject if we are able to derive a single actual('Standard') 	|
10789 	  |    shipment.							|
10790 	  +---------------------------------------------------------------------*/
10791 
10792             SELECT line_location_id
10793             INTO l_po_line_location_id
10794             FROM po_line_locations pll
10795            WHERE po_header_id = l_po_header_id
10796             AND po_line_id = l_po_line_id
10797 	    AND
10798 	     (
10799 	      (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
10800 	       ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
10801 	        (pll.payment_type IS NULL)
10802                )
10803               ) OR
10804 	      (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and
10805 	       ((pll.payment_type IS NOT NULL and pll.shipment_type <> 'PREPAYMENT') or
10806 		(pll.payment_type IS NULL)
10807 	       )
10808               )
10809              );
10810 
10811         EXCEPTION
10812           WHEN NO_DATA_FOUND Then
10813                 NULL;
10814 
10815           WHEN TOO_MANY_ROWS Then
10816 
10817             debug_info :=
10818               '(v_check_line_po_info 32.2) Too many po shipments';
10819             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10820               AP_IMPORT_UTILITIES_PKG.Print(
10821                    AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10822             END IF;
10823 
10824             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10825                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10826                      p_invoice_lines_rec.invoice_line_id,
10827                 'NO PO SHIPMENT NUM',
10828                  p_default_last_updated_by,
10829                  p_default_last_update_login,
10830                  current_calling_sequence) <> TRUE) THEN
10831                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10832                    AP_IMPORT_UTILITIES_PKG.Print(
10833                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
10834                    'insert_rejections<-'||current_calling_sequence);
10835                END IF;
10836                 RAISE check_po_failure;
10837             END IF;
10838             l_current_invoice_status := 'N';
10839 
10840         END;
10841 
10842       END IF; -- step 31 - CASE 2: po_line_location_id IS still null
10843 
10844     END IF; -- Step 31 - po_header_id and po_line_id are not null
10845 
10846 
10847     ---------------------------------------------------------------------------
10848     -- 31.1 - Amount Based Matching
10849     -- If match basis is still null derive it based po_line_location_id
10850     -- if it is not null. Complex Work Project matching basis will be
10851     -- poulated at shipment level.
10852     ---------------------------------------------------------------------------
10853     IF (l_po_line_location_id IS NOT NULL) THEN
10854       debug_info := '(v_check_line_po_info 31.1) Get Match Basis Based '||
10855                                   'on line_location_id';
10856       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10857         AP_IMPORT_UTILITIES_PKG.Print(
10858           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10859       END IF;
10860 
10861       SELECT pll.matching_basis
10862         INTO l_match_basis
10863         FROM po_line_locations pll
10864        WHERE pll.line_location_id = l_po_line_location_id;
10865 
10866     END IF;
10867 
10868 
10869     ---------------------------------------------------------------------------
10870     -- 31.2: Check for Corrupt PO data - Amount Based Matching
10871     -- Forward Bug 3253594. Po team made the po_line_id, line_location_id,
10872     -- code_combination_id and quantity_ordered fields of the po_distributions
10873     -- table nullable for certain types of PO's (i.e. Blanket Agreements and
10874     -- Global Agreements). These fields must be not not null in the types of
10875     -- PO's that the 'Payables Open Interface Import' concurrent program
10876     -- handles. Thus, if a distribution with any of these fields null is
10877     -- encountered then we can import the invoice because it references
10878     -- corrupt po distributions
10879     -- Complex Work Project. Matching Basis will be derived from po shipment.
10880     ---------------------------------------------------------------------------
10881 
10882     IF (l_po_header_id IS NOT NULL) THEN
10883       debug_info := '(v_check_line_po_info 31.2) Check for corrupt PO data';
10884       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10885         AP_IMPORT_UTILITIES_PKG.Print(
10886           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
10887       END IF;
10888 
10889      --start of bug 5292782
10890      declare
10891      l_blanket varchar2(10);
10892      begin
10893      select type_lookup_code, vendor_id  -- Bug 5448579
10894      into   l_blanket, l_vendor_id
10895      from po_headers
10896      where po_header_id=l_po_header_id;
10897      --end of select for 5292782
10898 
10899       SELECT COUNT(*)
10900         INTO l_corrupt_po_distributions
10901         FROM po_distributions
10902        WHERE po_header_id = l_po_header_id
10903          AND (line_location_id IS NULL
10904               OR po_line_id IS NULL
10905               OR code_combination_id IS NULL)
10906          AND  rownum = 1;  -- Bug 5448579
10907 
10908       IF (l_corrupt_po_distributions = 0) THEN
10909 
10910         SELECT COUNT(*)
10911           INTO l_corrupt_po_distributions
10912           FROM po_distributions pod,
10913                po_line_locations pll
10914          WHERE pod.po_header_id = l_po_header_id
10915            AND pod.line_location_id = pll.line_location_id
10916            AND ((pll.matching_basis = 'QUANTITY'
10917                 AND pod.quantity_ordered IS NULL)
10918              OR (pll.matching_basis = 'AMOUNT'
10919                 AND pod.amount_ordered IS NULL))
10920            AND rownum = 1; -- Bug 5448579
10921 
10922       END IF;
10923 
10924      IF (l_blanket<>'BLANKET') THEN --bug 5292782
10925       IF (l_corrupt_po_distributions > 0) THEN
10926         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
10927                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
10928                         p_invoice_lines_rec.invoice_line_id,
10929                         'INVALID PO NUM',
10930                         p_default_last_updated_by,
10931                         p_default_last_update_login,
10932                         current_calling_sequence,
10933                         'Y',
10934                         'CORRUPT PONUMBER',
10935                         l_po_header_id) <> TRUE) THEN
10936           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10937                 AP_IMPORT_UTILITIES_PKG.Print(
10938                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
10939                     'insert_rejections<-'||current_calling_sequence);
10940           END IF;
10941           RAISE check_po_failure;
10942         END IF;
10943 
10944         l_current_invoice_status := 'N';
10945 
10946       END IF;
10947      END IF;--Bug 5292782
10948      end; --Bug 5292782
10949 
10950     END IF;
10951 
10952     -- Misc Checks Here
10953     -- At this point we should have all the information in
10954     -- terms of id's
10955 
10956     -------------------------------------------------------------------
10957     -- Step 33   Misc Checks
10958     -- 1. Verify there is no vendor mismatch between invoice and PO
10959     -- 2. Verify that if it is a blanket PO, then release information was
10960     --    provided.  Otherwise, reject.
10961     -- 3. Verify that all PO info provided is correct i.e. points to
10962     --    existing PO data.  Otherwise, reject.
10963     -- 4. If no shipment info could be derived (either there is no shipments
10964     --    for the provided po data or too many) reject.
10965     -- 5. Verify if invoice currency is the same as PO currency and
10966     --    reject otherwise.
10967     -------------------------------------------------------------------
10968     IF (l_po_header_id IS NOT NULL) Then
10969 
10970       debug_info := '(v_check_line_po_info 33.1) Find if PO vendor does not '
10971                      ||'match interface vendor:Get PO Vendor';
10972       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10973           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10974                                         debug_info);
10975       END IF;
10976      -- Bug 5448579. L_vendor_id is already derived
10977     /*  SELECT vendor_id
10978         INTO l_vendor_id
10979         FROM po_headers
10980        WHERE po_header_id = l_po_header_id; */
10981 
10982       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10983           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10984           '------------------> l_vendor_id :per PO = '||
10985           to_char(l_vendor_id));
10986       END IF;
10987       debug_info :=
10988         '(v_check_line_po_info 33.1) Check for Inconsistent PO Vendor.';
10989       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
10990           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
10991                                       debug_info);
10992       END IF;
10993 
10994       IF (l_vendor_id <> nvl(p_invoice_rec.vendor_id, l_vendor_id)) THEN
10995         IF ( AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY' ) THEN
10996            BEGIN
10997 
10998              SELECT vendor_name
10999                INTO l_invoice_vendor_name
11000                FROM po_vendors
11001               WHERE vendor_id = p_invoice_rec.vendor_id;
11002 
11003              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11004                          AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11005                        p_invoice_lines_rec.invoice_line_id,
11006                        'INCONSISTENT PO SUPPLIER',
11007                         p_default_last_updated_by,
11008                         p_default_last_update_login,
11009                        current_calling_sequence,
11010                        'Y',
11011                        'SUPPLIER NAME',
11012                        l_invoice_vendor_name) <> TRUE) THEN
11013 
11014                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11015                  AP_IMPORT_UTILITIES_PKG.Print(
11016                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
11017                       'insert_rejections<-'||current_calling_sequence);
11018                END IF;
11019                 RAISE check_po_failure;
11020          END IF;
11021 
11022            EXCEPTION
11023              WHEN NO_DATA_FOUND THEN
11024                NULL;
11025            END;
11026 
11027         ELSE
11028           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11029                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11030                      p_invoice_lines_rec.invoice_line_id,
11031                     'INCONSISTENT PO SUPPLIER',
11032                     p_default_last_updated_by,
11033                      p_default_last_update_login,
11034                     current_calling_sequence) <> TRUE) THEN
11035 
11036                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11037                    AP_IMPORT_UTILITIES_PKG.Print(
11038                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
11039                      'insert_rejections<-'||current_calling_sequence);
11040                 END IF;
11041                 RAISE check_po_failure;
11042           END IF;
11043 
11044         END IF;  -- g_source = 'XML GATEWAY'
11045 
11046           l_current_invoice_status := 'N';
11047 
11048       END IF; -- vendor_id in po_header is different than in invoice record
11049 
11050       IF ((p_invoice_lines_rec.release_num IS NULL) AND
11051           (l_po_release_id IS NULL)) THEN
11052       DECLARE
11053          l_blanket varchar2(10); --4019310
11054       BEGIN
11055          l_blanket:='BLANKET'; --4019310
11056 
11057          debug_info := '(v_check_line_po_info 33.2) Find if PO is BLANKET';
11058           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11059             AP_IMPORT_UTILITIES_PKG.Print(
11060              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11061           END IF;
11062 
11063           SELECT 'Y'
11064             INTO l_po_is_not_blanket
11065             FROM po_headers
11066            WHERE po_header_id = l_po_header_id
11067              AND type_lookup_code <> l_blanket; --4019310
11068 
11069         EXCEPTION
11070       WHEN NO_DATA_FOUND THEN
11071             -- po header is BLANKET
11072             -- bug 2581097 added contextual information for XML GATEWAY
11073 
11074             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11075                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11076                         p_invoice_lines_rec.invoice_line_id,
11077                         'RELEASE MISSING',
11078                         p_default_last_updated_by,
11079                         p_default_last_update_login,
11080                         current_calling_sequence,
11081                         'Y',
11082                         'PO NUMBER',
11083                         l_po_number) <> TRUE) THEN
11084               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11085                      AP_IMPORT_UTILITIES_PKG.Print(
11086                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11087                        'insert_rejections<-'||current_calling_sequence);
11088               END IF;
11089               RAISE check_po_failure;
11090             END IF;
11091             l_current_invoice_status := 'N';
11092         END;
11093 
11094       END IF; -- release info is null
11095 
11096       IF ((l_po_line_id IS NOT NULL) AND
11097           (l_po_release_id IS NOT NULL) AND
11098           (l_po_line_location_id is NOT NULL)) THEN
11099 
11100         BEGIN
11101 
11102           debug_info :=
11103             '(v_check_line_po_info 33.3) Find if PO info is consistent';
11104           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11105             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11106                                         debug_info);
11107           END IF;
11108 
11109           SELECT 'X'
11110             INTO l_po_is_not_blanket
11111             FROM po_line_locations pll,
11112              po_releases pr
11113            WHERE pr.po_header_id = l_po_header_id
11114              AND pr.po_release_id = l_po_release_id
11115              AND pll.po_release_id = pr.po_release_id
11116              AND pll.po_line_id = l_po_line_id
11117              AND pll.line_location_id = l_po_line_location_id;
11118 
11119           EXCEPTION
11120           WHEN NO_DATA_FOUND THEN
11121             -- Reject
11122             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11123                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11124                         p_invoice_lines_rec.invoice_line_id,
11125                         'INVALID PO INFO',
11126                         p_default_last_updated_by,
11127                         p_default_last_update_login,
11128                         current_calling_sequence,
11129                         'Y',
11130                         'PO RECEIPT NUMBER',
11131                         p_invoice_lines_rec.receipt_number,
11132                         'PO NUMBER',
11133                         p_invoice_lines_rec.po_number,
11134                         'PO LINE NUMBER',
11135                         p_invoice_lines_rec.po_line_number,
11136                         'PO SHIPMENT NUMBER',
11137                         p_invoice_lines_rec.po_shipment_num,
11138                         'PO RELEASE NUMBER',
11139                         p_invoice_lines_rec.release_num ) <> TRUE) THEN
11140               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11141                      AP_IMPORT_UTILITIES_PKG.Print(
11142                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11143                        'insert_rejections<-'||current_calling_sequence);
11144               END IF;
11145               RAISE check_po_failure;
11146 
11147             END IF;
11148 
11149             l_current_invoice_status := 'N';
11150           END;
11151 
11152       END IF; -- po_line_id, po_release_id and po_line_location_id not null
11153 
11154       ---------------------------------------------------------
11155       -- Check if invoice currency is the same as PO currency
11156       ---------------------------------------------------------
11157       BEGIN
11158         debug_info := '(v_check_line_po_info 33.5) Check if inv curr is same is '
11159                       ||'po curr';
11160         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11161           AP_IMPORT_UTILITIES_PKG.Print(
11162               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
11163         END IF;
11164 
11165         SELECT 'Y'
11166           INTO l_po_inv_curr_is_consis_flag
11167           FROM po_headers
11168          WHERE po_header_id = l_po_header_id
11169            AND currency_code = p_invoice_rec.invoice_currency_code;
11170       EXCEPTION
11171         WHEN NO_DATA_FOUND THEN
11172         debug_info :=
11173           '(v_check_line_po_info 33.5) Reject: Inconsistent currencies';
11174           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11175             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11176                                         debug_info);
11177           END IF;
11178           -- Reject
11179           IF ( AP_IMPORT_INVOICES_PKG.g_source = 'XML GATEWAY') THEN
11180             SELECT currency_code
11181               INTO l_po_currency_code
11182               FROM po_headers
11183              WHERE po_header_id = l_po_header_id ;
11184 
11185             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11186                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11187                          p_invoice_lines_rec.invoice_line_id,
11188                          'INCONSISTENT CURR',
11189                          p_default_last_updated_by,
11190                          p_default_last_update_login,
11191                          current_calling_sequence,
11192                         'Y',
11193                         'INVOICE CURRENCY CODE',
11194                          p_invoice_rec.invoice_currency_code,
11195                         'PO CURRENCY CODE',
11196                          l_po_currency_code ) <> TRUE) THEN
11197 
11198               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11199                 AP_IMPORT_UTILITIES_PKG.Print(
11200                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11201                        'insert_rejections<-'||current_calling_sequence);
11202               END IF;
11203                RAISE check_po_failure;
11204                END IF;
11205 
11206           ELSE
11207 
11208             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11209                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11210                       p_invoice_lines_rec.invoice_line_id,
11211                     'INCONSISTENT CURR',
11212                      p_default_last_updated_by,
11213                      p_default_last_update_login,
11214                       current_calling_sequence) <> TRUE) THEN
11215 
11216               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11217                 AP_IMPORT_UTILITIES_PKG.Print(
11218                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11219                        'insert_rejections<-'||current_calling_sequence);
11220               END IF;
11221                RAISE check_po_failure;
11222 
11223             END IF;
11224 
11225           END IF; -- g_source = 'XML GATEWAY'
11226 
11227           l_current_invoice_status := 'N';
11228 
11229         END;
11230 
11231     END IF; -- Step 33 - Misc checks: po_header_id is not null
11232 
11233 
11234   --------------------------------------------------------
11235   -- Step 34.1
11236   -- Check price correction information
11237   -- Retropricing: Please Note that the code for Price
11238   -- Corrections should not be executed for source = 'PPA'.
11239   -- For PPA Lines p_invoice_lines_rec.price_correction_flag
11240   -- should be NULL
11241   ---------------------------------------------------------
11242   IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
11243     IF p_invoice_lines_rec.price_correction_flag = 'Y' then
11244 
11245      debug_info := '(v_check_line_po_info 34.1) Check for price correction information on'||
11246      			' prepayment invoices';
11247      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11248        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11249                                      debug_info);
11250      END IF;
11251 
11252      IF(p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT') THEN
11253 
11254          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11255             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11256                 p_invoice_lines_rec.invoice_line_id,
11257                 'CANNOT PRICE CORRECT PREPAY',
11258                 p_default_last_updated_by,
11259                 p_default_last_update_login,
11260                 current_calling_sequence)<> TRUE) THEN
11261 
11262             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11263                      AP_IMPORT_UTILITIES_PKG.Print(
11264 	                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
11265                                 'insert_rejections<-'||current_calling_sequence);
11266             END IF;
11267 
11268             RAISE check_po_failure;
11269 
11270          END IF;
11271 
11272          l_current_invoice_status := 'N';
11273 
11274       END IF;
11275 
11276       debug_info := '(v_check_line_po_info 34.2) Check price correction information';
11277       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11278           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11279                                       debug_info);
11280       END IF;
11281 
11282       IF p_invoice_lines_rec.price_correct_inv_num is null then
11283 
11284         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11285               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11286               p_invoice_lines_rec.invoice_line_id,
11287               'PRICE CORRECT INV NUM REQUIRED',
11288               p_default_last_updated_by,
11289               p_default_last_update_login,
11290               current_calling_sequence)<> TRUE) THEN
11291 
11292           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11293                AP_IMPORT_UTILITIES_PKG.Print(
11294                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11295                  'insert_rejections<-'||current_calling_sequence);
11296           END IF;
11297 
11298           RAISE check_po_failure;
11299         END IF;
11300 
11301         l_current_invoice_status := 'N';
11302 
11303       END IF;
11304 
11305 
11306     --Check if price_correct_inv_line_num is NULL, if so reject the invoice.
11307     IF p_invoice_lines_rec.price_correct_inv_line_num is null then
11308 
11309        debug_info := '(v_check_line_po_info 34.3) Check price correction line information';
11310        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11311           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11312                                       debug_info);
11313        END IF;
11314 
11315        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11316               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11317               p_invoice_lines_rec.invoice_line_id,
11318               'INCOMPLETE PO INFO',
11319               p_default_last_updated_by,
11320               p_default_last_update_login,
11321               current_calling_sequence)<> TRUE) THEN
11322 
11323          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11324                AP_IMPORT_UTILITIES_PKG.Print(
11325                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11326                  'insert_rejections<-'||current_calling_sequence);
11327          END IF;
11328          RAISE check_po_failure;
11329        END IF;
11330        l_current_invoice_status := 'N';
11331 
11332     END IF;
11333 
11334     --check if this is a valid invoice and invoice line is provided
11335     --for a price correction
11336     IF (p_invoice_lines_rec.price_correct_inv_num is not null and
11337         p_invoice_lines_rec.price_correct_inv_line_num is not null) THEN
11338      BEGIN
11339 
11340       debug_info := '(v_check_line_po_info 34.4) Check if price correcting invoice line'
11341 		    ||'is valid';
11342       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11343         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11344                                       debug_info);
11345       END IF;
11346 
11347       SELECT DISTINCT ai.invoice_id, ail.amount
11348       INTO l_price_correct_inv_id, l_base_match_amount
11349       FROM ap_invoices ai, ap_invoice_lines ail, ap_invoice_distributions aid
11350       WHERE ai.invoice_num = p_invoice_lines_rec.price_correct_inv_num
11351       AND ail.invoice_id = ai.invoice_id
11352       AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num
11353       AND aid.invoice_id = ail.invoice_id
11354       AND aid.po_distribution_id is not null
11355       AND aid.corrected_invoice_dist_id is null
11356       AND nvl(ail.discarded_flag,'N') = 'N'
11357       AND nvl(ail.cancelled_flag,'N') = 'N'
11358       AND ai.vendor_id = p_invoice_rec.vendor_id
11359       AND rownum <= 1;
11360 
11361 
11362     EXCEPTION
11363       WHEN NO_DATA_FOUND THEN
11364        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11365               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11366               p_invoice_lines_rec.invoice_line_id,
11367               'INVALID PO INFO',
11368               p_default_last_updated_by,
11369               p_default_last_update_login,
11370               current_calling_sequence)<> TRUE) THEN
11371          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11372                      AP_IMPORT_UTILITIES_PKG.Print(
11373                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11374                        'insert_rejections<-'||current_calling_sequence);
11375          END IF;
11376          RAISE check_po_failure;
11377        END IF;
11378        l_current_invoice_status := 'N';
11379     END;
11380 
11381    END IF;
11382 
11383    --Check match_basis. Amount Based  Matching.
11384    --Match Basis is already dervied in section 31.1
11385    IF (l_price_correct_inv_id IS NOT NULL
11386 	and p_invoice_lines_rec.price_correct_inv_line_num IS NOT NULL) THEN
11387      BEGIN
11388 
11389        debug_info := '(v_check_line_po_info 34.5) Check if price correction line is matched to'
11390 			||' a service order shipment';
11391        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11392          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11393                                        debug_info);
11394        END IF;
11395 
11396 
11397        IF (l_match_basis = 'AMOUNT') THEN
11398 
11399            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11400                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11401                 p_invoice_lines_rec.invoice_line_id,
11402                 'INCONSISTENT PO INFO',
11403                 p_default_last_updated_by,
11404                 p_default_last_update_login,
11405                 current_calling_sequence)<> TRUE) THEN
11406 
11407                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
11408 
11409                      AP_IMPORT_UTILITIES_PKG.Print(
11410                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11411                        'insert_rejections<-'||current_calling_sequence);
11412 
11413                 END IF;
11414 
11415                 RAISE check_po_failure;
11416 
11417            END IF;
11418 
11419 	   l_current_invoice_status := 'N';
11420 
11421         END IF;
11422      EXCEPTION WHEN OTHERS THEN
11423        NULL;
11424      END;
11425 
11426    END IF;  /* check match_basis */
11427 
11428 
11429    IF l_po_distribution_id is not null then
11430 
11431       debug_info := '(v_check_line_po_info 34.6) Check pc invoice is matched '
11432                     ||'to po dist';
11433        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11434         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11435                                       debug_info);
11436       END IF;
11437 
11438       BEGIN
11439         --the query below will ensure the invoice has at least one base matched
11440         --distribution matched to this po distribution
11441 
11442         SELECT 'Y'
11443         INTO    l_pc_inv_valid
11444         FROM    ap_invoice_distributions
11445         WHERE   invoice_id = l_price_correct_inv_id
11446 	AND     invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num
11447         AND     po_distribution_id = l_po_distribution_id;
11448 
11449       EXCEPTION
11450         WHEN NO_DATA_FOUND THEN
11451           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11452               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11453               p_invoice_lines_rec.invoice_line_id,
11454               'INVALID PO INFO',
11455               p_default_last_updated_by,
11456               p_default_last_update_login,
11457               current_calling_sequence)<> TRUE) THEN
11458 
11459             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11460               AP_IMPORT_UTILITIES_PKG.Print(
11461               AP_IMPORT_INVOICES_PKG.g_debug_switch,
11462               'insert_rejections<-'||current_calling_sequence);
11463             END IF;
11464             RAISE check_po_failure;
11465           END IF;
11466           l_current_invoice_status := 'N';
11467         WHEN TOO_MANY_ROWS THEN
11468           NULL;
11469       END;
11470 
11471     END IF;
11472 
11473 
11474     IF (l_po_distribution_id is null and
11475         l_po_line_location_id is not null) THEN
11476 
11477       debug_info := '(v_check_line_po_info 34.7) Check pc invoice is matched'
11478                     ||' to shipment';
11479        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11480         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11481                                       debug_info);
11482       END IF;
11483 
11484       BEGIN
11485         --the query below will ensure the invoice has at least one base matched
11486         --distribution matched to one of the po dists for this shipment
11487 
11488         SELECT 'Y'
11489           INTO l_pc_inv_valid
11490           FROM ap_invoice_distributions
11491          WHERE invoice_id = l_price_correct_inv_id
11492            AND invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num
11493            AND po_distribution_id IN (
11494                  SELECT po_distribution_id
11495                    FROM po_distributions
11496                    WHERE line_location_id = l_po_line_location_id);
11497 
11498       EXCEPTION
11499         WHEN NO_DATA_FOUND THEN
11500           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11501                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11502                 p_invoice_lines_rec.invoice_line_id,
11503                'INVALID PO INFO',
11504                 p_default_last_updated_by,
11505                 p_default_last_update_login,
11506                 current_calling_sequence)<> TRUE) THEN
11507             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11508                      AP_IMPORT_UTILITIES_PKG.Print(
11509                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11510                        'insert_rejections<-'||current_calling_sequence);
11511             END IF;
11512             RAISE check_po_failure;
11513           END IF;
11514           l_current_invoice_status := 'N';
11515         WHEN TOO_MANY_ROWS THEN
11516           NULL;
11517       END;
11518 
11519     END IF;
11520 
11521 
11522     --No price corrections should not be performed against finally closed POs.
11523     BEGIN
11524 
11525        debug_info := '(v_check_line_po_info 34.8) Check if po shipment is finally closed';
11526        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11527          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11528                                       debug_info);
11529        END IF;
11530 
11531        SELECT 'Y'
11532        INTO l_shipment_finally_closed
11533        FROM ap_invoice_lines ail, po_line_locations pll
11534        WHERE ail.invoice_id = l_price_correct_inv_id
11535        AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num
11536        AND pll.line_location_id = ail.po_line_location_id
11537        AND pll.closed_code = 'FINALLY CLOSED';
11538 
11539        IF (nvl(l_shipment_finally_closed,'N') = 'Y') THEN
11540 
11541 	  IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11542                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11543                 p_invoice_lines_rec.invoice_line_id,
11544                 'INVALID PO INFO',
11545                 p_default_last_updated_by,
11546                 p_default_last_update_login,
11547                 current_calling_sequence)<> TRUE) THEN
11548 
11549               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
11550 
11551                      AP_IMPORT_UTILITIES_PKG.Print(
11552                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11553                        'insert_rejections<-'||current_calling_sequence);
11554 
11555               END IF;
11556               RAISE check_po_failure;
11557 
11558           END IF;
11559 
11560           l_current_invoice_status := 'N';
11561 
11562        END IF;
11563 
11564     EXCEPTION
11565        WHEN OTHERS THEN
11566 	  NULL;
11567 
11568     END ;
11569 
11570 
11571     --Quantity Invoiced must be always be positive or NULL for price corrections regardless of
11572     --the invoice type.
11573     debug_info := '(v_check_line_po_info 34.9) Check if Quantity_Invoiced for the price corrections'
11574 			||'to be either NULL or positive';
11575     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11576          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11577                                       debug_info);
11578     END IF;
11579 
11580     IF (p_invoice_lines_rec.quantity_invoiced IS NOT NULL AND
11581   	p_invoice_lines_rec.quantity_invoiced < 0) THEN
11582 
11583       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11584                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11585                 p_invoice_lines_rec.invoice_line_id,
11586                 'INVALID PO INFO',
11587                 p_default_last_updated_by,
11588                 p_default_last_update_login,
11589                 current_calling_sequence)<> TRUE) THEN
11590 
11591            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
11592 
11593                      AP_IMPORT_UTILITIES_PKG.Print(
11594                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11595                        'insert_rejections<-'||current_calling_sequence);
11596 
11597            END IF;
11598            RAISE check_po_failure;
11599 
11600        END IF;
11601 
11602        l_current_invoice_status := 'N';
11603 
11604     END IF;
11605 
11606 
11607     --Unit Price must be always be positive for STANDARD invoices, and negative
11608     --for CREDIT/DEBIT memos, and postive or negative for MIXED type of invoices.
11609     debug_info := '(v_check_line_po_info 34.10) Check the sign of the unit_price against'
11610 		  ||'the invoice type';
11611     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11612          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11613                                       debug_info);
11614     END IF;
11615 
11616     --Contract Payments: Modified the IF condition to add 'PREPAYMENT'.
11617 
11618     IF ((p_invoice_rec.invoice_type_lookup_code IN ('STANDARD','PREPAYMENT') and
11619          p_invoice_lines_rec.unit_price < 0) OR
11620         (p_invoice_rec.invoice_type_lookup_code IN ('CREDIT','DEBIT') and
11621 	 p_invoice_lines_rec.unit_price > 0)) THEN
11622 
11623       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11624                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11625                 p_invoice_lines_rec.invoice_line_id,
11626                 'INVALID PO INFO',
11627                 p_default_last_updated_by,
11628                 p_default_last_update_login,
11629                 current_calling_sequence)<> TRUE) THEN
11630 
11631            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
11632 
11633                      AP_IMPORT_UTILITIES_PKG.Print(
11634                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11635                        'insert_rejections<-'||current_calling_sequence);
11636 
11637            END IF;
11638            RAISE check_po_failure;
11639 
11640        END IF;
11641 
11642        l_current_invoice_status := 'N';
11643 
11644     END IF;
11645 
11646     BEGIN
11647 
11648       debug_info := '(v_check_line_po_info 34.11) Check if quantity_invoiced for price correction'
11649 		  ||' exceeds the quantity_invoiced on the base match';
11650 
11651       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11652          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11653                                       debug_info);
11654       END IF;
11655 
11656       BEGIN
11657 
11658          SELECT ail.quantity_invoiced
11659          INTO l_base_match_quantity
11660          FROM ap_invoice_lines ail
11661          WHERE ail.invoice_id = l_price_correct_inv_id
11662          AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num;
11663 
11664 
11665       --bugfix:5640388
11666        EXCEPTION
11667          WHEN NO_DATA_FOUND THEN
11668             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11669        			       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11670                        	       p_invoice_lines_rec.invoice_line_id,
11671                                'PRICE CORRECT INV INVALID',
11672 	                       p_default_last_updated_by,
11673 			       p_default_last_update_login,
11674 			       current_calling_sequence)<> TRUE) THEN
11675 	       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11676 	           AP_IMPORT_UTILITIES_PKG.Print(
11677 	                          AP_IMPORT_INVOICES_PKG.g_debug_switch,
11678 	                          'insert_rejections<-'||current_calling_sequence);
11679 																								                 END IF;
11680 	             RAISE check_po_failure;
11681                END IF;
11682                l_current_invoice_status := 'N';
11683          WHEN TOO_MANY_ROWS THEN
11684            NULL;
11685          END;
11686 
11687 
11688       IF ( p_invoice_lines_rec.quantity_invoiced > l_base_match_quantity) THEN
11689 
11690          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11691                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11692                 p_invoice_lines_rec.invoice_line_id,
11693                 'AMOUNT BILLED BELOW ZERO',
11694                 p_default_last_updated_by,
11695                 p_default_last_update_login,
11696                 current_calling_sequence)<> TRUE) THEN
11697 
11698              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
11699 
11700                      AP_IMPORT_UTILITIES_PKG.Print(
11701                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11702                        'insert_rejections<-'||current_calling_sequence);
11703 
11704              END IF;
11705              RAISE check_po_failure;
11706 
11707           END IF;
11708 
11709           l_current_invoice_status := 'N';
11710 
11711       END IF;
11712 
11713      END ;
11714 
11715 
11716     --Amount_Billed against the Purchase Order Shipment should not go below 0 IN
11717     --absolute terms and relative to the base match. The amount billed for the
11718     --base match should be calculated based on quantity being corrected and any
11719     --previous existing price corrections against the base match.
11720     BEGIN
11721 
11722       debug_info := '(v_check_line_po_info 34.12) Check if amount_billed against PO Shipment/Dist'
11723 		  ||'goes below zero due to this price correction relative to the base match';
11724 
11725 
11726       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11727          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11728                                       debug_info);
11729       END IF;
11730 
11731       l_line_amt_calculated :=
11732       nvl(ap_utilities_pkg.ap_round_currency(
11733            p_invoice_lines_rec.unit_price*
11734            p_invoice_lines_rec.quantity_invoiced,
11735            p_invoice_rec.invoice_currency_code)
11736           ,0);
11737 
11738       IF (p_invoice_lines_rec.amount < 0 OR l_line_amt_calculated < 0) THEN
11739 
11740          BEGIN
11741 
11742             SELECT nvl(sum(ail.amount),0)
11743             INTO l_correction_amount
11744             FROM ap_invoice_lines ail
11745             WHERE ail.invoice_id = l_price_correct_inv_id
11746             AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num
11747             AND ail.match_type IN ('PRICE_CORRECTION','QTY_CORRECTION');
11748 
11749 	    --bugfix:5640388
11750 	    EXCEPTION
11751 	        WHEN NO_DATA_FOUND THEN
11752 	            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11753 	                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11754 	                     p_invoice_lines_rec.invoice_line_id,
11755 	                     'PRICE CORRECT INV INVALID',
11756 	                     p_default_last_updated_by,
11757 	                     p_default_last_update_login,
11758 	                     current_calling_sequence)<> TRUE) THEN
11759 	                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11760 	                        AP_IMPORT_UTILITIES_PKG.Print(
11761 	                                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
11762 	                                  'insert_rejections<-'||current_calling_sequence);
11763 	                  END IF;
11764 	                 RAISE check_po_failure;
11765 		     END IF;
11766 		     l_current_invoice_status := 'N';
11767 	        WHEN TOO_MANY_ROWS THEN
11768 	            NULL;
11769 	END;
11770 
11771         IF (abs(nvl(p_invoice_lines_rec.amount,l_line_amt_calculated)) >
11772 	 				(l_base_match_amount + l_correction_amount)) THEN
11773 
11774            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11775                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11776                 p_invoice_lines_rec.invoice_line_id,
11777                 'AMOUNT BILLED BELOW ZERO',
11778                 p_default_last_updated_by,
11779                 p_default_last_update_login,
11780                 current_calling_sequence)<> TRUE) THEN
11781 
11782              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
11783 
11784                      AP_IMPORT_UTILITIES_PKG.Print(
11785                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
11786                        'insert_rejections<-'||current_calling_sequence);
11787 
11788              END IF;
11789              RAISE check_po_failure;
11790 
11791            END IF;
11792 
11793            l_current_invoice_status := 'N';
11794 
11795          END IF;
11796 
11797        END IF; /* p_invoice_lines_rec.line_amount < 0 */
11798 
11799     END ;
11800 
11801 
11802 
11803     --make sure we won't reduce the amount billed below zero on
11804     --the po dists relative to the base match
11805     --this requires we use the proration logic used in the matching code
11806     --which, for price corrections, is to prorate based upon amount if the
11807     --quantity billed on the po is zero, otherwise prorate by quantity billed
11808 
11809     IF  l_po_distribution_id IS NULL AND
11810         l_po_line_location_id IS NOT NULL AND
11811         (nvl(p_invoice_lines_rec.amount,0) < 0 OR
11812         l_line_amt_calculated < 0) THEN
11813 
11814       debug_info := '(v_check_line_po_info 34.13) Ensure amount billed on po '
11815                      ||'distributions wont be reduced below zero for shipment';
11816       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11817         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11818                                       debug_info);
11819       END IF;
11820 
11821       BEGIN
11822 
11823          SELECT amount, quantity_invoiced
11824          INTO l_total_amount_invoiced, l_total_quantity_invoiced
11825          FROM ap_invoice_lines ail
11826          WHERE ail.invoice_id = l_price_correct_inv_id
11827          AND ail.line_number = p_invoice_lines_rec.price_correct_inv_line_num;
11828 
11829          --bugfix:5640388
11830          EXCEPTION
11831 	   WHEN NO_DATA_FOUND THEN
11832 	      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11833 	                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11834 	                     p_invoice_lines_rec.invoice_line_id,
11835 	                     'PRICE CORRECT INV INVALID',
11836 	                     p_default_last_updated_by,
11837 	                     p_default_last_update_login,
11838 	                     current_calling_sequence)<> TRUE) THEN
11839 	          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11840 	               AP_IMPORT_UTILITIES_PKG.Print(
11841 	                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
11842 	                       'insert_rejections<-'||current_calling_sequence);
11843 	          END IF;
11844 	          RAISE check_po_failure;
11845 	      END IF;
11846 	      l_current_invoice_status := 'N';
11847           WHEN TOO_MANY_ROWS THEN
11848              NULL;
11849       END;
11850 
11851       IF l_total_quantity_invoiced = 0 THEN
11852         IF (l_total_amount_invoiced + l_correction_amount + nvl(p_invoice_lines_rec.amount,l_line_amt_calculated) < 0) THEN
11853 
11854                IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11855                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11856                      p_invoice_lines_rec.invoice_line_id,
11857                      'AMOUNT BILLED BELOW ZERO',
11858                      p_default_last_updated_by,
11859                      p_default_last_update_login,
11860                      current_calling_sequence)<> TRUE) THEN
11861 
11862                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11863                       AP_IMPORT_UTILITIES_PKG.Print(
11864                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
11865                          'insert_rejections<-'||current_calling_sequence);
11866                  END IF;
11867                  RAISE check_po_failure;
11868                END IF;
11869                l_current_invoice_status := 'N';
11870 
11871          END IF;
11872       END IF;
11873 
11874 
11875       IF l_total_quantity_invoiced > 0 then
11876 
11877         FOR pc_inv_dists IN (SELECT quantity_invoiced, amount, invoice_distribution_id
11878 			    FROM ap_invoice_distributions
11879 			    WHERE invoice_id = l_price_correct_inv_id
11880 			    AND invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num)
11881 
11882         LOOP
11883 
11884 	  BEGIN
11885 
11886              SELECT sum(aid.amount)
11887              INTO l_correction_dist_amount
11888 	     FROM ap_invoice_distributions aid
11889              WHERE corrected_invoice_dist_id = pc_inv_dists.invoice_distribution_id
11890 	     GROUP BY corrected_invoice_dist_id ;
11891 
11892           EXCEPTION WHEN OTHERS THEN
11893 	     l_correction_dist_amount := 0;
11894           END ;
11895 
11896           IF (pc_inv_dists.quantity_invoiced/ l_total_quantity_invoiced *
11897               p_invoice_lines_rec.amount + l_correction_dist_amount + pc_inv_dists.amount) < 0 OR
11898              (pc_inv_dists.quantity_invoiced/ l_total_quantity_invoiced *
11899               l_line_amt_calculated + l_correction_dist_amount + pc_inv_dists.amount) < 0  THEN
11900 
11901              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11902                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11903                  p_invoice_lines_rec.invoice_line_id,
11904                  'AMOUNT BILLED BELOW ZERO',
11905                  p_default_last_updated_by,
11906                  p_default_last_update_login,
11907                  current_calling_sequence)<> TRUE)  THEN
11908                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11909                    AP_IMPORT_UTILITIES_PKG.Print(
11910                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
11911                    'insert_rejections<-'||current_calling_sequence);
11912                END IF;
11913                RAISE check_po_failure;
11914              END IF;
11915              l_current_invoice_status := 'N';
11916 
11917           END IF;
11918 
11919         END LOOP;
11920 
11921        END IF;
11922 
11923      END IF;  --end of checking if the qty billed on the shipment's dists
11924              --will fall below zero relative to the base match distribution's amount_billed
11925 
11926 
11927 
11928     --Make sure we won't reduce the amount billed below zero on the po dist absolutely
11929     IF (l_po_distribution_id IS NOT NULL AND
11930         (nvl(p_invoice_lines_rec.amount,0) < 0 OR
11931          l_line_amt_calculated < 0)) THEN
11932 
11933       debug_info := '(v_check_line_po_info 34.14) Ensure amount billed on po '
11934                     ||'dist wont be reduced below zero, l_po_distribution_id is: '||l_po_distribution_id;
11935       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11936         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
11937                                       debug_info);
11938       END IF;
11939 
11940    BEGIN
11941       BEGIN
11942 	--Contract Payments: Modified the SELECT clause
11943         SELECT decode(distribution_type,'PREPAYMENT',nvl(amount_financed,0),nvl(amount_billed,0))
11944         INTO l_pc_po_amt_billed
11945         FROM po_distributions
11946         WHERE po_distribution_id = l_po_distribution_id
11947           AND line_location_id IS NOT NULL; /* BUG 3253594 */
11948 
11949       --bugfix:5640388
11950       EXCEPTION
11951         WHEN NO_DATA_FOUND THEN
11952            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11953                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11954                    p_invoice_lines_rec.invoice_line_id,
11955                    'PRICE CORRECT INV INVALID',
11956                    p_default_last_updated_by,
11957                    p_default_last_update_login,
11958                    current_calling_sequence)<> TRUE) THEN
11959                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11960                     AP_IMPORT_UTILITIES_PKG.Print(
11961                               AP_IMPORT_INVOICES_PKG.g_debug_switch,
11962                               'insert_rejections<-'||current_calling_sequence);
11963                 END IF;
11964                 RAISE check_po_failure;
11965            END IF;
11966            l_current_invoice_status := 'N';
11967         WHEN TOO_MANY_ROWS THEN
11968            NULL;
11969         END;
11970 
11971         IF (l_pc_po_amt_billed + nvl(p_invoice_lines_rec.amount,0) < 0) or
11972            (l_pc_po_amt_billed + l_line_amt_calculated < 0) then
11973 
11974            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
11975               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
11976               p_invoice_lines_rec.invoice_line_id,
11977               'AMOUNT BILLED BELOW ZERO',
11978               p_default_last_updated_by,
11979               p_default_last_update_login,
11980               current_calling_sequence)<> TRUE) THEN
11981              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
11982                AP_IMPORT_UTILITIES_PKG.Print(
11983                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
11984                   'insert_rejections<-'||current_calling_sequence);
11985              END IF;
11986              RAISE check_po_failure;
11987            END IF;
11988            l_current_invoice_status := 'N';
11989         END IF;
11990 
11991       EXCEPTION
11992         WHEN NO_DATA_FOUND THEN
11993           NULL;
11994       END;
11995 
11996     END IF;
11997 
11998 
11999     --make sure we won't reduce the amount billed below zero on the po dists
12000     --this requires we use the proration logic used in the matching code
12001     --which, for price corrections, is to prorate based upon amount if the
12002     --quantity billed on the po is zero, otherwise prorate by quantity billed
12003 
12004     IF  l_po_distribution_id IS NULL AND
12005         l_po_line_location_id IS NOT NULL AND
12006         (nvl(p_invoice_lines_rec.amount,0) < 0 OR
12007         l_line_amt_calculated < 0) THEN
12008 
12009       debug_info := '(v_check_line_po_info 34.15) Ensure amount billed on po '
12010                      ||'distribtuions wont be reduced below zero for shipment';
12011       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12012         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12013                                       debug_info);
12014       END IF;
12015 
12016 
12017       --Contract Payments: Modified the SELECT clause
12018       BEGIN
12019 
12020         SELECT nvl(SUM(decode(distribution_type,'PREPAYMENT',nvl(amount_financed,0),nvl(amount_billed,0))),0),
12021                nvl(SUM(decode(distribution_type,'PREPAYMENT',nvl(quantity_financed,0),nvl(quantity_billed,0))),0)
12022         INTO l_total_amount_billed, l_total_quantity_billed
12023         FROM po_distributions
12024         WHERE line_location_id = l_po_line_location_id
12025         AND po_distribution_id IN (SELECT po_distribution_id
12026                                  FROM   ap_invoice_distributions
12027                                  WHERE  invoice_id = l_price_correct_inv_id
12028 				 AND    invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num);
12029 
12030         --bugfix:5640388
12031        EXCEPTION
12032           WHEN NO_DATA_FOUND THEN
12033               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12034                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12035                       p_invoice_lines_rec.invoice_line_id,
12036                       'PRICE CORRECT INV INVALID',
12037                       p_default_last_updated_by,
12038                       p_default_last_update_login,
12039                       current_calling_sequence)<> TRUE) THEN
12040                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12041                        AP_IMPORT_UTILITIES_PKG.Print(
12042                                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
12043                                     'insert_rejections<-'||current_calling_sequence);
12044                    END IF;
12045                    RAISE check_po_failure;
12046                END IF;
12047                l_current_invoice_status := 'N';
12048           WHEN TOO_MANY_ROWS THEN
12049                NULL;
12050        END;
12051 
12052        IF l_total_quantity_billed = 0 THEN
12053         IF (l_total_amount_billed + nvl(p_invoice_lines_rec.amount,0) < 0) OR
12054            (l_total_amount_billed + l_line_amt_calculated < 0) THEN
12055 
12056                IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12057                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12058                      p_invoice_lines_rec.invoice_line_id,
12059                      'AMOUNT BILLED BELOW ZERO',
12060                      p_default_last_updated_by,
12061                      p_default_last_update_login,
12062                      current_calling_sequence)<> TRUE) THEN
12063 
12064                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12065                       AP_IMPORT_UTILITIES_PKG.Print(
12066                           AP_IMPORT_INVOICES_PKG.g_debug_switch,
12067                          'insert_rejections<-'||current_calling_sequence);
12068                  END IF;
12069                  RAISE check_po_failure;
12070                END IF;
12071                l_current_invoice_status := 'N';
12072 
12073          END IF;
12074       END IF;
12075 
12076 
12077       IF l_total_quantity_billed > 0 then
12078 
12079 	--Contract Payments: Modified the SELECT clause
12080         FOR pc_po_dists IN (SELECT decode(pod.distribution_type,'PREPAYMENT',nvl(pod.quantity_financed,0),
12081 					 nvl(pod.quantity_billed,0)) quantity_billed,
12082 				   decode(pod.distribution_type,'PREPAYMENT',nvl(pod.amount_financed,0),
12083 				         nvl(pod.amount_billed,0)) amount_billed
12084                             FROM po_distributions pod
12085                             WHERE pod.line_location_id = l_po_line_location_id
12086                             AND pod.po_distribution_id IN (
12087                                  SELECT aid.po_distribution_id
12088                                  FROM ap_invoice_distributions aid
12089                                  WHERE  aid.invoice_id = l_price_correct_inv_id
12090 			         AND   aid.invoice_line_number = p_invoice_lines_rec.price_correct_inv_line_num))
12091         LOOP
12092 
12093           IF (pc_po_dists.quantity_billed / l_total_quantity_billed *
12094               p_invoice_lines_rec.amount + pc_po_dists.amount_billed) < 0 OR
12095              (pc_po_dists.quantity_billed / l_total_quantity_billed *
12096               l_line_amt_calculated + pc_po_dists.amount_billed) < 0  THEN
12097 
12098              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12099                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12100                  p_invoice_lines_rec.invoice_line_id,
12101                  'AMOUNT BILLED BELOW ZERO',
12102                  p_default_last_updated_by,
12103                  p_default_last_update_login,
12104                  current_calling_sequence)<> TRUE)  THEN
12105                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12106                    AP_IMPORT_UTILITIES_PKG.Print(
12107                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
12108                    'insert_rejections<-'||current_calling_sequence);
12109                END IF;
12110                RAISE check_po_failure;
12111              END IF;
12112              l_current_invoice_status := 'N';
12113 
12114           END IF;
12115 
12116         END LOOP;
12117 
12118        END IF;
12119 
12120      END IF;  --end of checking if the qty billed on the shipment's dists
12121              --will fall below zero
12122 
12123    END IF;   -- p_price_correction_flag = 'Y'
12124 
12125  END IF ; /* g_source <> 'PPA' */
12126 
12127 --Bug 5225547 added the following
12128  -------------------------------------------------------------------------
12129   -- Validate Match Option if populated
12130   -------------------------------------------------------------------------
12131   If ( l_po_line_location_id is  null) and  (l_po_number is not null) and  ( p_invoice_lines_rec.po_shipment_num is not null) then
12132          BEGIN
12133                 SELECT po_header_id
12134                 INTO l_po_header_id
12135                 FROM po_headers
12136                 WHERE segment1 = l_po_number
12137                 AND type_lookup_code in ('BLANKET', 'PLANNED', 'STANDARD');
12138          EXCEPTION
12139          when NO_DATA_FOUND then
12140          null;
12141          END;
12142 
12143         BEGIN
12144                 SELECT po_line_id
12145                 INTO l_po_line_id
12146                 FROM po_lines
12147                 WHERE po_header_id = l_po_header_id
12148                 AND ROWNUM <= 1;
12149         EXCEPTION
12150         when NO_DATA_FOUND then
12151         null;
12152         END;
12153 
12154          BEGIN
12155                 SELECT line_location_id
12156                 INTO l_po_line_location_id
12157                 FROM po_line_locations
12158                 WHERE po_header_id = l_po_header_id
12159                 AND po_line_id = l_po_line_id
12160                 AND shipment_num = p_invoice_lines_rec.po_shipment_num ;
12161         EXCEPTION
12162          when NO_DATA_FOUND then
12163          null;
12164          END;
12165 
12166   End if;
12167 IF (l_po_line_location_id IS NULL) THEN
12168 
12169      IF (l_po_distribution_id IS NOT NULL) THEN
12170         BEGIN
12171 
12172             SELECT line_location_id
12173             INTO l_po_line_location_id
12174             FROM po_distributions
12175             WHERE po_distribution_id = l_po_distribution_id;
12176 
12177         EXCEPTION
12178         WHEN NO_DATA_FOUND THEN
12179  NULL;
12180   END;
12181 
12182      END IF;
12183  END IF;
12184 
12185   If ( l_po_line_location_id is not null) then
12186 
12187       debug_info := '(v_check_line_po_info) :Get Match Option from po shipment';
12188       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12189         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12190                                       debug_info);
12191       END IF;
12192 
12193         Select nvl(match_option,'P')
12194         Into l_temp_match_option
12195         From po_line_locations
12196         Where line_location_id = l_po_line_location_id;
12197     If (l_temp_match_option is not null) then
12198         If ( p_invoice_lines_rec.match_option is not null and   p_invoice_lines_rec.match_option <> l_temp_match_option) then
12199 
12200 
12201           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12202               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12203               p_invoice_lines_rec.invoice_line_id,
12204               'INVALID MATCH OPTION',
12205               p_default_last_updated_by,
12206               p_default_last_update_login,
12207               current_calling_sequence) <> TRUE) THEN
12208 
12209               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12210                AP_IMPORT_UTILITIES_PKG.Print(
12211                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
12212                  'insert_rejections<-'||current_calling_sequence);
12213                END IF;
12214                 raise check_po_failure;
12215            End if;
12216            l_current_invoice_status := 'N';
12217 
12218         End if;
12219 
12220         p_invoice_lines_rec.match_option := nvl(l_temp_match_option , p_invoice_lines_rec.match_option);
12221 
12222     End if;
12223  End if;
12224 
12225 --End of bug 5225547
12226 
12227 
12228 
12229     --------------------------------------------------------------------
12230     -- Rest of the PO Validation should be done now
12231     --------------------------------------------------------------------
12232  IF (l_current_invoice_status <>'N') THEN
12233 
12234       ---------------------------------------------------------
12235       -- Step 35
12236       -- check for additional PO validation
12237       ---------------------------------------------------------
12238       debug_info := '(v_check_line_po_info 35) Call v_check_line_po_info2';
12239       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12240         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12241                                       debug_info);
12242       END IF;
12243 
12244       IF (AP_IMPORT_VALIDATION_PKG.v_check_line_po_info2 (
12245          p_invoice_rec,                                             -- IN
12246          p_invoice_lines_rec,                                     -- IN
12247          p_positive_price_tolerance,                               -- IN
12248          p_qty_ord_tolerance,                                     -- IN
12249 	 p_amt_ord_tolerance,					  -- IN
12250          p_max_qty_ord_tolerance,                                 -- IN
12251 	 p_max_amt_ord_tolerance,				  -- IN
12252          p_po_header_id           => l_po_header_id,                -- IN
12253          p_po_line_id            => l_po_line_id,                     -- IN
12254          p_po_line_location_id => l_po_line_location_id,         -- IN
12255          p_po_distribution_id  => l_po_distribution_id,             -- IN
12256          p_match_option           => l_match_option,             -- OUT NOCOPY
12257          p_calc_quantity_invoiced => l_calc_quantity_invoiced,   -- OUT NOCOPY
12258          p_calc_unit_price          => l_calc_unit_price,        -- OUT NOCOPY
12259          p_calc_line_amount         => l_calc_line_amount,       -- OUT NOCOPY /* ABM */
12260          p_default_last_updated_by => p_default_last_updated_by, -- IN
12261          p_default_last_update_login => p_default_last_update_login,  -- IN
12262          p_current_invoice_status   => l_current_invoice_status,      -- IN OUT
12263          p_match_basis             =>  l_match_basis,        -- IN /*Amount Based Matching */
12264              p_calling_sequence         => current_calling_sequence) <> TRUE )THEN
12265         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12266           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12267            'v_check_po_line_info2<-' ||current_calling_sequence);
12268         END IF;
12269         RAISE check_po_failure;
12270       END IF;
12271 
12272       --
12273       -- show output values (only if debug_switch = 'Y')
12274       --
12275       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12276         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12277         '------------------> l_current_invoice_status = '||
12278         l_current_invoice_status);
12279       END IF;
12280 
12281       --------------------------------------------------------
12282       -- Step 36
12283       -- PO Overlay.
12284       -- Retropricing: PO Overlay is not needed for PPA's
12285       ---------------------------------------------------------
12286       IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
12287           debug_info := '(v_check_line_po_info 36) Call v_check_po_overlay';
12288           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12289             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12290                                          debug_info);
12291           END IF;
12292 
12293           IF (AP_IMPORT_VALIDATION_PKG.v_check_po_overlay(
12294 		p_invoice_rec,					   -- IN
12295                 p_invoice_lines_rec,                               -- IN
12296                 NVL(l_po_line_id, p_invoice_lines_rec.po_line_id), -- IN
12297                 NVL(l_po_line_location_id,
12298                     p_invoice_lines_rec.po_line_location_id),      -- IN
12299                 NVL(l_po_distribution_id,
12300                     p_invoice_lines_rec.po_distribution_id),       -- IN
12301                 p_set_of_books_id,                                   -- IN
12302                 p_default_last_updated_by,                         -- IN
12303                 p_default_last_update_login,                       -- IN
12304                 p_current_invoice_status   => l_current_invoice_status, -- IN OUT
12305                 p_calling_sequence         => current_calling_sequence) <> TRUE )THEN
12306             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12307               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12308                       'v_check_po_overlay<-' ||current_calling_sequence);
12309             END IF;
12310             RAISE check_po_failure;
12311           END IF;
12312 
12313           --
12314           -- show output values (only if debug_switch = 'Y')
12315           --
12316           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12317             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12318              '------------------> l_current_invoice_status = '||
12319              l_current_invoice_status);
12320           END IF;
12321       END IF; ---source <> PPA
12322      END IF; -- Step 35 and Step 36: Invoice Status <> 'N'
12323 
12324    END IF; -- Step 29: Invoice Status <> 'N'
12325 
12326 
12327  ELSIF (p_invoice_lines_rec.line_type_lookup_code IN ('FREIGHT','MISCELLANEOUS','TAX')) THEN
12328 
12329    IF(p_invoice_lines_rec.price_correction_flag = 'Y') THEN
12330 
12331 
12332 	debug_info := '(v_check_line_po_info 37) Cannot associate charge lines with price corrections';
12333         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12334           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12335                                       debug_info);
12336         END IF;
12337 
12338         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12339               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12340               p_invoice_lines_rec.invoice_line_id,
12341               'INVALID PO INFO',
12342               p_default_last_updated_by,
12343               p_default_last_update_login,
12344               current_calling_sequence) <> TRUE) THEN
12345 
12346            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12347                AP_IMPORT_UTILITIES_PKG.Print(
12348                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
12349                  'insert_rejections<-'||current_calling_sequence);
12350            END IF;
12351 
12352            RAISE check_po_failure;
12353 
12354          END IF;
12355 
12356          l_current_invoice_status := 'N';
12357 
12358     END IF;
12359 
12360  END IF; /*nvl(p_invoice_lines_rec.line_type_lookup_code, 'ITEM'... */
12361   --
12362   -- Return value
12363   p_current_invoice_status := l_current_invoice_status;
12364 
12365   IF (l_po_header_id IS NOT NULL) Then
12366     p_invoice_lines_rec.po_header_id := l_po_header_id;
12367   End IF;
12368 
12369   IF (l_po_release_id IS NOT NULL) then
12370     p_invoice_lines_rec.po_release_id := l_po_release_id;
12371   END IF;
12372 
12373   IF (l_po_line_id IS NOT NULL) then
12374     p_invoice_lines_rec.po_line_id := l_po_line_id;
12375   END IF;
12376 
12377   IF (l_po_line_location_id IS NOT NULL) Then
12378     p_invoice_lines_rec.po_line_location_id := l_po_line_location_id;
12379   END IF;
12380 
12381   IF (l_po_distribution_id IS NOT NULL) THEN
12382     p_invoice_lines_rec.po_distribution_id := l_po_distribution_id;
12383   END IF;
12384 
12385   IF (l_match_option IS NOT NULL AND
12386     p_invoice_lines_rec.match_option IS NULL) THEN
12387     p_invoice_lines_rec.match_option := l_match_option;
12388   END IF;
12389 
12390   IF (l_calc_quantity_invoiced IS NOT NULL AND
12391     p_invoice_lines_rec.quantity_invoiced IS NULL) then
12392     p_invoice_lines_rec.quantity_invoiced := l_calc_quantity_invoiced;
12393   END IF;
12394 
12395   IF (l_calc_unit_price IS NOT NULL AND
12396     p_invoice_lines_rec.unit_price is NULL) then
12397     p_invoice_lines_rec.unit_price := l_calc_unit_price;
12398   END IF;
12399 
12400   /* Amount Based Matching */
12401   IF (l_calc_line_amount IS NOT NULL AND
12402     p_invoice_lines_rec.amount is NULL) then
12403     p_invoice_lines_rec.amount := l_calc_line_amount;
12404   END IF;
12405 
12406   /* Bug 5400087 */
12407   --7045958
12408   IF (p_invoice_lines_rec.rcv_transaction_id IS NOT NULL AND p_invoice_lines_rec.match_option = 'R') THEN
12409     IF (l_match_basis = 'AMOUNT') THEN
12410       p_invoice_lines_rec.match_type := 'ITEM_TO_SERVICE_RECEIPT';
12411     ELSE
12412       p_invoice_lines_rec.match_type := 'ITEM_TO_RECEIPT';
12413     END IF;
12414   ELSE
12415     IF (p_invoice_lines_rec.po_line_location_id IS NOT NULL) THEN
12416       IF (l_match_basis = 'AMOUNT') THEN
12417         p_invoice_lines_rec.match_type := 'ITEM_TO_SERVICE_PO';
12418       ELSE
12419         p_invoice_lines_rec.match_type := 'ITEM_TO_PO';
12420       END IF;
12421     END IF;
12422   END IF;
12423 
12424   IF (p_invoice_lines_rec.price_correction_flag = 'Y') THEN
12425     p_invoice_lines_rec.corrected_inv_id := l_price_correct_inv_id;
12426     p_invoice_lines_rec.match_type := 'PRICE_CORRECTION'; /* 5400087 */
12427   END IF;
12428 
12429   RETURN (TRUE);
12430 
12431 EXCEPTION
12432 
12433   WHEN OTHERS THEN
12434     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12435       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12436                                     debug_info);
12437     END IF;
12438 
12439     IF (SQLCODE < 0) then
12440       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12441         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12442                                       SQLERRM);
12443       END IF;
12444     END IF;
12445     RETURN(FALSE);
12446 
12447 END v_check_line_po_info;
12448 
12449 
12450 -----------------------------------------------------------------------------
12451 -- This function is used to validate PO information at line level.
12452 --
12453 FUNCTION v_check_line_po_info2 (
12454     p_invoice_rec         IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
12455     p_invoice_lines_rec   IN  AP_IMPORT_INVOICES_PKG.r_line_info_rec,
12456     p_positive_price_tolerance     IN             NUMBER,
12457     p_qty_ord_tolerance            IN             NUMBER,
12458     p_amt_ord_tolerance		   IN		  NUMBER,
12459     p_max_qty_ord_tolerance        IN             NUMBER,
12460     p_max_amt_ord_tolerance	   IN		  NUMBER,
12461     p_po_header_id                   IN             NUMBER,
12462     p_po_line_id                   IN                NUMBER,
12463     p_po_line_location_id           IN               NUMBER,
12464     p_po_distribution_id           IN               NUMBER,
12465     p_match_option                       OUT NOCOPY VARCHAR2,
12466     p_calc_quantity_invoiced           OUT NOCOPY NUMBER,
12467     p_calc_unit_price                  OUT NOCOPY NUMBER,
12468     p_calc_line_amount                 OUT NOCOPY NUMBER, /* Amount Based Matching */
12469     p_default_last_updated_by      IN             NUMBER,
12470     p_default_last_update_login    IN             NUMBER,
12471     p_current_invoice_status       IN  OUT NOCOPY  VARCHAR2,
12472     p_match_basis                  IN             VARCHAR2, /* Amount Based matching */
12473     p_calling_sequence             IN             VARCHAR2) RETURN BOOLEAN
12474 IS
12475 
12476 check_po_failure          EXCEPTION;
12477 l_po_header_id              NUMBER := nvl(p_invoice_lines_rec.po_header_id,
12478                                         p_po_header_id);
12479 l_po_line_id              NUMBER := nvl(p_invoice_lines_rec.po_line_id,
12480                                         p_po_line_id);
12481 l_po_line_location_id      NUMBER := nvl(p_invoice_lines_rec.po_line_location_id,
12482                                         p_po_line_location_id);
12483 l_po_distribution_id      NUMBER := nvl(p_invoice_lines_rec.po_distribution_id,
12484                                         p_po_distribution_id);
12485 l_unit_price              NUMBER := p_invoice_lines_rec.unit_price;
12486 l_po_unit_price              NUMBER;
12487 l_dec_unit_price          NUMBER;
12488 l_unit_of_measure          VARCHAR2(25) := 'N';
12489 l_current_invoice_status  VARCHAR2(1)  := p_current_invoice_status;
12490 l_price_break              VARCHAR2(1);
12491 l_calc_line_amount          NUMBER:=0;
12492 l_overbill                  VARCHAR2(1);
12493 l_qty_based_rejection     VARCHAR2(1);
12494 l_amt_based_rejection	  VARCHAR2(1);
12495 l_quantity_invoiced          NUMBER;
12496 l_qty_invoiced              NUMBER;
12497 l_total_qty_billed          NUMBER;
12498 l_quantity_outstanding      NUMBER;
12499 l_quantity_ordered          NUMBER;
12500 l_qty_already_billed      NUMBER;
12501 l_amount_outstanding      NUMBER;
12502 l_amount_ordered          NUMBER;
12503 l_amt_already_billed      NUMBER;
12504 l_outstanding		  NUMBER;
12505 l_ordered		  NUMBER;
12506 l_already_billed	  NUMBER;
12507 l_po_line_matching_basis  PO_LINES_ALL.MATCHING_BASIS%TYPE;
12508 l_invalid_shipment_type      VARCHAR2(1):= '';
12509 l_invalid_shipment_count  NUMBER;
12510 l_positive_price_variance NUMBER;
12511 l_total_match_amount      NUMBER;
12512 l_temp_match_option          VARCHAR2(25);
12513 current_calling_sequence  VARCHAR2(2000);
12514 debug_info                 VARCHAR2(500);
12515 l_line_amount             NUMBER;  /* Amount Based Matching */
12516 l_temp_shipment_type      PO_LINE_LOCATIONS_ALL.SHIPMENT_TYPE%TYPE;
12517 
12518 BEGIN
12519 
12520   -- Update the calling sequence
12521   --
12522   current_calling_sequence:= 'AP_IMPORT_VALIDATION_PKG.v_check_line_po_info2<-'
12523                              ||P_calling_sequence;
12524 
12525   l_qty_based_rejection := 'N';
12526   l_amt_based_rejection := 'N';
12527 
12528   -----------------------------------------------------------
12529   -- Step 1
12530   -- Check for Active PO
12531   -----------------------------------------------------------
12532   IF ((l_po_header_id IS NOT NULL) AND
12533       (l_po_line_id IS NOT NULL)) THEN
12534 
12535      l_quantity_invoiced := NULL;  --Bug 7446306 - For the Fixed Price Service PO the TERV line is not generated as this is not
12536                               -- initialized to NULL.
12537 
12538     IF (l_po_distribution_id IS NOT NULL) Then
12539       debug_info := '(v_check_line_po_info2 1) Check Valid Shipment Type from '
12540                     ||'l_po_distribution_id ';
12541       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12542         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12543                                 debug_info);
12544       END IF;
12545 
12546       BEGIN
12547 
12548 	--Contract Payments: Modified the WHERE condition so that we check for
12549         --'Prepayment' type shipments for complex work pos for Prepayment invoices and otherwise
12550         --Standard/Blanket/Scheduled shipments are valid for Standard/Credit invoices.
12551         SELECT 'X'
12552             INTO l_invalid_shipment_type
12553           FROM po_distributions pd,
12554                po_line_locations pll
12555          WHERE pd.line_location_id   = pll.line_location_id
12556            AND pd.po_distribution_id = l_po_distribution_id
12557            AND
12558              (
12559               (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and
12560 	       pll.SHIPMENT_TYPE IN ('STANDARD','BLANKET','SCHEDULED')
12561               ) OR
12562               (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
12563                ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
12564                 (pll.payment_type IS NULL and pll.shipment_type IN ('STANDARD','BLANKET','SCHEDULED'))
12565                )
12566               )
12567              )
12568            AND pll.APPROVED_FLAG     = 'Y'
12569            AND (nvl(pll.CLOSED_CODE, 'OPEN') <> 'FINALLY CLOSED')
12570            AND nvl(pll.consigned_flag,'N')   <> 'Y';
12571       EXCEPTION
12572         WHEN NO_DATA_FOUND Then
12573           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12574                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12575                 p_invoice_lines_rec.invoice_line_id,
12576                 'INVALID SHIPMENT TYPE',
12577                 p_default_last_updated_by,
12578                 p_default_last_update_login,
12579                 current_calling_sequence) <> TRUE) THEN
12580             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12581                 AP_IMPORT_UTILITIES_PKG.Print(
12582                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
12583                   'insert_rejections<-'||current_calling_sequence);
12584             END IF;
12585              RAISE check_po_failure;
12586           END IF;
12587           --
12588           l_current_invoice_status := 'N';
12589 
12590       END;
12591 
12592     ELSIF (l_po_line_location_id IS NOT NULL) THEN
12593       -- elsif to po_distribution_id is not null
12594 
12595       debug_info := '(v_check_line_po_info2 1) Check Valid Shipment Type from '
12596                     ||'l_po_line_location_id ';
12597       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12598         AP_IMPORT_UTILITIES_PKG.Print(
12599           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
12600       END IF;
12601 
12602       --Contract Payments: Modified the WHERE condition so that we check for
12603       --'Prepayment' type shipments for complex work pos for Prepayment invoices and otherwise
12604       --Standard/Blanket/Scheduled shipments are valid for Standard/Credit invoices.
12605       BEGIN
12606         SELECT    'X'
12607           INTO  l_invalid_shipment_type
12608           FROM  po_line_locations pll
12609          WHERE  line_location_id = l_po_line_location_id
12610            AND(
12611                (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and
12612 	        pll.SHIPMENT_TYPE IN ('STANDARD','BLANKET','SCHEDULED')
12613                ) OR
12614                (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
12615                 ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
12616                  (pll.payment_type IS NULL and pll.shipment_type IN ('STANDARD','BLANKET','SCHEDULED'))
12617                 )
12618                )
12619               )
12620            AND  APPROVED_FLAG    = 'Y'
12621            AND  (nvl(CLOSED_CODE, 'OPEN') <> 'FINALLY CLOSED')
12622            AND  nvl(consigned_flag,'N')   <> 'Y';
12623 
12624       EXCEPTION
12625         WHEN NO_DATA_FOUND Then
12626           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12627             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12628             p_invoice_lines_rec.invoice_line_id,
12629             'INVALID SHIPMENT TYPE',
12630             p_default_last_updated_by,
12631             p_default_last_update_login,
12632             current_calling_sequence) <> TRUE) THEN
12633             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12634               AP_IMPORT_UTILITIES_PKG.Print(
12635                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
12636                   'insert_rejections<-'||current_calling_sequence);
12637             END IF;
12638              RAISE check_po_failure;
12639             END IF;
12640           --
12641           l_current_invoice_status := 'N';
12642 
12643       END;
12644 
12645       -------------------------------------------------------------------------
12646       -- Validate Match Option if populated
12647       -------------------------------------------------------------------------
12648       IF ( l_po_line_location_id is not null) THEN
12649         debug_info := '(v_check_line_po_info2) :Get Match Option from po shipment';
12650         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12651             AP_IMPORT_UTILITIES_PKG.Print(
12652               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
12653         END IF;
12654 
12655         SELECT nvl(match_option,'P')
12656           INTO l_temp_match_option
12657              FROM po_line_locations
12658          WHERE line_location_id = l_po_line_location_id;
12659 
12660           IF (p_invoice_lines_rec.match_option IS NOT NULL AND
12661               p_invoice_lines_rec.match_option <> l_temp_match_option) THEN
12662 
12663             -- Reject for invalid Match option
12664             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12665                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12666                 p_invoice_lines_rec.invoice_line_id,
12667                 'INVALID MATCH OPTION',
12668                 p_default_last_updated_by,
12669                 p_default_last_update_login,
12670                 current_calling_sequence)<> TRUE) Then
12671               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12672                 AP_IMPORT_UTILITIES_PKG.Print(
12673                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
12674                  'insert_rejections <-'||current_calling_sequence);
12675               END IF;
12676           RAISE check_po_failure;
12677             END IF;
12678           l_current_invoice_status := 'N';
12679 
12680           END IF;
12681 
12682         -- set the ouput parameter
12683         p_match_option := nvl(l_temp_match_option ,
12684                               p_invoice_lines_rec.match_option);
12685       END IF; -- if l_po_line_location_id is not null
12686 
12687     ELSIF ((l_po_line_id IS NOT NULL) AND
12688            (l_po_line_location_id IS NULL)) Then
12689            -- elsif to po_distribution_id is not null
12690       debug_info := '(v_check_line_po_info2 1) Check Valid Shipment Type from'
12691                     ||' l_po_line_id ';
12692       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12693         AP_IMPORT_UTILITIES_PKG.Print(
12694           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
12695       END IF;
12696 
12697       BEGIN
12698         SELECT count(*)
12699           INTO l_invalid_shipment_count
12700           FROM po_line_locations pll
12701          WHERE pll.po_line_id = l_po_line_id
12702           AND(
12703 	      (
12704                (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and
12705 	        pll.SHIPMENT_TYPE NOT IN ('STANDARD','BLANKET','SCHEDULED')
12706                ) OR
12707                (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
12708                 ((pll.payment_type IS NOT NULL and pll.shipment_type <> 'PREPAYMENT') or
12709                  (pll.payment_type IS NULL and pll.shipment_type NOT IN ('STANDARD','BLANKET','SCHEDULED'))
12710                 )
12711                )
12712               )
12713              /* Bug 4038403 removed these two conditions and added the below condition
12714               OR (APPROVED_FLAG <> 'Y')
12715               OR (APPROVED_FLAG IS NULL) */
12716 
12717               OR nvl(APPROVED_FLAG, 'N') <> 'Y'
12718             )
12719             OR (nvl(CLOSED_CODE, 'OPEN') = 'FINALLY CLOSED')
12720             OR (nvl(consigned_flag,'N') = 'Y');
12721 
12722           IF (l_invalid_shipment_count > 0) Then
12723             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12724                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12725                 p_invoice_lines_rec.invoice_line_id,
12726                 'INVALID SHIPMENT TYPE',
12727                 p_default_last_updated_by,
12728                 p_default_last_update_login,
12729                 current_calling_sequence) <> TRUE) THEN
12730                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12731                   AP_IMPORT_UTILITIES_PKG.Print(
12732                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
12733                     'insert_rejections<-'||current_calling_sequence);
12734                END IF;
12735                 RAISE check_po_failure;
12736             END IF;
12737             --
12738             l_current_invoice_status := 'N';
12739 
12740           END IF;
12741 
12742       EXCEPTION
12743         WHEN NO_DATA_FOUND Then
12744         NULL;
12745       END;
12746 
12747       -- Check for PO line price break
12748       -- Cannot have a line level match if price break is on
12749       -- Retropricing: Don't know what this rejection means???.
12750       -- For PPA's irrespective of the fact if the line has price breaks
12751       -- or not, we should not reject it. Price breaks is a feature in PO
12752       -- and AP does matching at the ship level.
12753       IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
12754           debug_info := '(v_check_line_po_info2 1) Check Price Break for PO '
12755                         ||'Line(Line Level Match) ';
12756           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12757               AP_IMPORT_UTILITIES_PKG.Print(
12758                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
12759           END IF;
12760           --
12761           BEGIN
12762             SELECT allow_price_override_flag
12763               INTO l_price_break
12764               FROM po_lines
12765              WHERE po_line_id = l_po_line_id;
12766 
12767               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12768                   AP_IMPORT_UTILITIES_PKG.Print(
12769                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
12770                     '------------------> l_price_break= '|| l_price_break);
12771               END IF;
12772               --
12773               IF (nvl(l_price_break,'N') ='Y' ) Then
12774                 IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12775                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12776                     p_invoice_lines_rec.invoice_line_id,
12777                     'LINE HAS PRICE BREAK',
12778                     p_default_last_updated_by,
12779                     p_default_last_update_login,
12780                     current_calling_sequence) <> TRUE) THEN
12781                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12782                       AP_IMPORT_UTILITIES_PKG.Print(
12783                        AP_IMPORT_INVOICES_PKG.g_debug_switch,
12784                        'insert_rejections<-'||current_calling_sequence);
12785                   END IF;
12786                     RAISE check_po_failure;
12787                   END IF;
12788                 --
12789                 l_current_invoice_status := 'N';
12790                 --
12791               END IF;
12792 
12793           EXCEPTION
12794             WHEN NO_DATA_FOUND Then
12795             Null;
12796 
12797           END;
12798           --
12799       END IF; -- source <> 'PPA'
12800     END IF; -- if to po_distribution_id is not null
12801 
12802     ---------------------------------------------------------------------------
12803     -- Step 1.1, Reject if po_inventory_item_id, p_vendor_item_num
12804     --                          and po_item_description are inconsistent
12805     --
12806     --  Added consistency check for Supplier Item Number too as part of
12807     --  the effort to support Supplier Item Number in Invoice Import
12808     --                                                         bug 1873251
12809     --  Amount Based Matching. Reject if any of the lines' match basis
12810     --  is Amount. However due to complex work project match basis will be
12811     --  at po shipment level hence all the matching basis related validation
12812     --  has been moved to shipment level.
12813     ---------------------------------------------------------------------------
12814 
12815     IF l_po_line_location_id IS NOT NULL THEN
12816 
12817        Select shipment_type
12818 	 Into l_temp_shipment_type
12819 	 From po_line_locations
12820 	Where line_location_id = l_po_line_location_id;
12821 
12822     END IF;
12823 
12824     IF ((p_invoice_lines_rec.vendor_item_num IS NOT NULL) AND
12825        (p_match_basis = 'AMOUNT') AND
12826        (nvl(l_temp_shipment_type,'X') <> 'PREPAYMENT')) THEN
12827       --
12828       debug_info := '(v_check_line_po_info2 1.1) Check inconsistency for '
12829                     ||'po_vendor_item_num '
12830                     ||'shipment level match basis is AMOUNT';
12831       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12832         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12833                                       debug_info);
12834       END IF;
12835       --
12836       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12837                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12838                         p_invoice_lines_rec.invoice_line_id,
12839                         'INCONSISTENT SHIPMENT INFO',
12840                         p_default_last_updated_by,
12841                         p_default_last_update_login,
12842                         current_calling_sequence,
12843                         'Y',
12844                         'SUPPLIER ITEM NUMBER',
12845                         p_invoice_lines_rec.vendor_item_num ) <> TRUE) THEN
12846         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12847              AP_IMPORT_UTILITIES_PKG.Print(
12848                AP_IMPORT_INVOICES_PKG.g_debug_switch,
12849                'insert_rejections<-'||current_calling_sequence);
12850         END IF;
12851         RAISE check_po_failure;
12852       END IF;
12853 
12854       l_current_invoice_status := 'N';
12855 
12856     ELSIF (((p_invoice_lines_rec.inventory_item_id IS NOT NULL) OR
12857           (p_invoice_lines_rec.item_description IS NOT NULL)) AND
12858           (p_match_basis = 'AMOUNT') AND
12859 	  (nvl(l_temp_shipment_type,'X') <> 'PREPAYMENT')) THEN
12860       --
12861       debug_info := '(v_check_line_po_info2 1.1) Check inconsistency for '
12862                     ||'po_inventory_item_id and po_item_description '
12863                     ||'shipment level match basis is AMOUNT';
12864       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12865         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
12866                                       debug_info);
12867       END IF;
12868       --
12869       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12870                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12871                         p_invoice_lines_rec.invoice_line_id,
12872                         'INCONSISTENT SHIPMENT INFO',
12873                         p_default_last_updated_by,
12874                         p_default_last_update_login,
12875                         current_calling_sequence ) <> TRUE) THEN
12876         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12877              AP_IMPORT_UTILITIES_PKG.Print(
12878                AP_IMPORT_INVOICES_PKG.g_debug_switch,
12879                'insert_rejections<-'||current_calling_sequence);
12880         END IF;
12881         RAISE check_po_failure;
12882       END IF;
12883 
12884       l_current_invoice_status := 'N';
12885 
12886     END IF;
12887 
12888     ------------------------------------------------------
12889     -- Step 2
12890     -- Check for Invalid Distribution Set with PO
12891     -- Retropricing: Distribution Set is always NULL for PPA's
12892     ------------------------------------------------------
12893     IF ((p_invoice_lines_rec.distribution_set_id is NOT NULL) OR
12894         (p_invoice_lines_rec.distribution_set_name is NOT NULL)) Then
12895         debug_info := '(v_check_line_po_info2 2) Check for Invalid '
12896                     ||'Distribution Set with PO';
12897       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12898         AP_IMPORT_UTILITIES_PKG.Print(
12899           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
12900       END IF;
12901 
12902       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
12903                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
12904                    p_invoice_lines_rec.invoice_line_id,
12905                    'INVALID DIST SET WITH PO',
12906                    p_default_last_updated_by,
12907                    p_default_last_update_login,
12908                    current_calling_sequence) <> TRUE) THEN
12909         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12910             AP_IMPORT_UTILITIES_PKG.Print(
12911               AP_IMPORT_INVOICES_PKG.g_debug_switch,
12912                  'insert_rejections<-'||current_calling_sequence);
12913         END IF;
12914         RAISE check_po_failure;
12915       END IF;
12916       l_current_invoice_status := 'N';
12917 
12918     END IF;
12919 
12920     -----------------------------------------------------
12921     -- Step 3
12922     -- Get Unit Price and UOM from PO Lines
12923     ------------------------------------------------------
12924     debug_info :=
12925       '(v_check_line_po_info2 3) Get Unit Price / UOM from PO Lines';
12926     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
12927         AP_IMPORT_UTILITIES_PKG.Print(
12928           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
12929     END IF;
12930     --
12931     --bug2878889.Commented the following code and added the code below.
12932 /*    IF (l_po_line_location_id IS NOT NULL) THEN
12933       SELECT pll.price_override, pll.unit_meas_lookup_code
12934         INTO l_po_unit_price,l_unit_of_measure
12935         FROM po_line_locations pll
12936         WHERE  pll.line_location_id = l_po_line_location_id;
12937     ELSE
12938       SELECT unit_price,unit_meas_lookup_code
12939         INTO l_po_unit_price,l_unit_of_measure
12940         FROM po_lines
12941        WHERE po_line_id = l_po_line_id;
12942     END IF;*/
12943 
12944     IF ((p_invoice_lines_rec.quantity_invoiced IS NULL)
12945              AND (l_po_unit_price IS NULL)
12946              AND (p_invoice_lines_rec.po_release_id IS NOT NULL) ) THEN
12947 
12948              SELECT NVL(price_override,unit_price),unit_meas_lookup_code
12949              INTO l_po_unit_price,l_unit_of_measure
12950              FROM po_line_locations_release_v
12951              WHERE po_line_id = l_po_line_id
12952 	     -- bug7328060, added the below condition
12953              AND line_location_id = nvl(l_po_line_location_id, line_location_id)
12954              AND po_release_id = p_invoice_lines_rec.po_release_id;
12955 
12956     ELSIF ( (l_po_line_location_id IS NOT NULL)
12957              AND (p_invoice_lines_rec.quantity_invoiced IS NULL)
12958              AND (l_po_unit_price IS NULL)
12959              AND (p_invoice_lines_rec.po_release_id IS NULL) ) THEN
12960 
12961              SELECT pll.price_override, pll.unit_meas_lookup_code
12962              INTO l_po_unit_price,l_unit_of_measure
12963              FROM po_line_locations pll
12964              WHERE  pll.line_location_id = l_po_line_location_id;
12965 
12966     ELSIF (  (l_po_line_id IS NOT NULL)
12967               AND  (p_invoice_lines_rec.quantity_invoiced IS NULL)
12968               AND (l_po_unit_price IS NULL)
12969               AND (p_invoice_lines_rec.po_release_id IS NULL) ) THEN
12970 
12971               SELECT unit_price,unit_meas_lookup_code
12972               INTO l_po_unit_price,l_unit_of_measure
12973               FROM po_lines
12974               WHERE po_line_id = l_po_line_id;
12975 
12976     ELSIF (   (p_invoice_lines_rec.quantity_invoiced IS NOT NULL)
12977              AND (l_po_line_id IS NOT NULL)
12978 	     AND (l_po_unit_price is NULL)
12979 	     AND (p_invoice_lines_rec.amount is NOT NULL)) THEN
12980 
12981               IF (p_invoice_lines_rec.quantity_invoiced=0) THEN
12982                  l_po_unit_price :=0;
12983              ELSE
12984   		 l_po_unit_price := ap_utilities_pkg.ap_round_currency (
12985   	        		    p_invoice_lines_rec.amount /
12986 				    p_invoice_lines_rec.quantity_invoiced,
12987 		                    p_invoice_rec.invoice_currency_code);
12988  	     END IF; --Bug6932650
12989 
12990 		SELECT unit_meas_lookup_code
12991 		INTO l_unit_of_measure
12992 		FROM po_lines
12993 		WHERE po_line_id = l_po_line_id;
12994 
12995     END IF;
12996     --bug2878889 ends
12997 
12998     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
12999         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13000                   '------------------>
13001                         l_po_unit_price = '||to_char(l_po_unit_price)
13002                         ||' l_unit_of_measure = '||l_unit_of_measure);
13003     END IF;
13004     --
13005     -----------------------------------------------------
13006     -- Step 4
13007     -- Check for Invalid Line Quantity
13008     -- For credits we can have -ve qty
13009     -- Amount Based Matching. Line Amount can not be -ve
13010     -- if match basis is 'AMOUNT'
13011     ------------------------------------------------------
13012     --Contract Payments: Modified the IF condition to add 'PREPAYMENT'.
13013 
13014     IF ((p_invoice_lines_rec.quantity_invoiced) <= 0 AND
13015         (p_invoice_rec.invoice_type_lookup_code IN ('STANDARD','PREPAYMENT'))) Then
13016       debug_info :=
13017         '(v_check_line_po_info2 4) Check for Invalid Line Quantity';
13018       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13019           AP_IMPORT_UTILITIES_PKG.Print(
13020             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13021       END IF;
13022 
13023       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13024             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13025             p_invoice_lines_rec.invoice_line_id,
13026             'INVALID QUANTITY',
13027             p_default_last_updated_by,
13028             p_default_last_update_login,
13029             current_calling_sequence,
13030             'Y',
13031             'QUANTITY INVOICED',
13032             p_invoice_lines_rec.quantity_invoiced) <> TRUE) THEN
13033         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13034             AP_IMPORT_UTILITIES_PKG.Print(
13035               AP_IMPORT_INVOICES_PKG.g_debug_switch,
13036                 'insert_rejections<-'||current_calling_sequence);
13037         END IF;
13038         RAISE check_po_failure;
13039       END IF;
13040 
13041       l_current_invoice_status := 'N';
13042 
13043     END IF;
13044 
13045     ELSIF (p_match_basis = 'AMOUNT') THEN
13046       IF ((p_invoice_lines_rec.amount) <= 0 AND
13047         (p_invoice_rec.invoice_type_lookup_code = 'STANDARD')) Then
13048          debug_info :=
13049           '(v_check_line_po_info2 4) Check for Invalid Line Amount';
13050         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13051            AP_IMPORT_UTILITIES_PKG.Print(
13052             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13053         END IF;
13054 
13055         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13056             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13057             p_invoice_lines_rec.invoice_line_id,
13058             'INVALID QUANTITY',
13059             p_default_last_updated_by,
13060             p_default_last_update_login,
13061             current_calling_sequence,
13062             'Y',
13063             'QUANTITY INVOICED',
13064             p_invoice_lines_rec.amount) <> TRUE) THEN
13065           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13066             AP_IMPORT_UTILITIES_PKG.Print(
13067               AP_IMPORT_INVOICES_PKG.g_debug_switch,
13068                 'insert_rejections<-'||current_calling_sequence);
13069           END IF;
13070           RAISE check_po_failure;
13071         END IF;
13072 
13073         l_current_invoice_status := 'N';
13074 
13075       END IF;
13076 
13077     END IF; -- end if match basis
13078 
13079     ------------------------------------------------------
13080     -- Step 5
13081     -- Check for Invalid Unit of Measure against PO Line
13082     -- Amount Based Matching. No need to check for UOM
13083     -- if match basis is 'AMOUNT'
13084     ------------------------------------------------------
13085     IF (p_match_basis = 'QUANTITY') THEN
13086     IF (p_invoice_lines_rec.unit_of_meas_lookup_code <> l_unit_of_measure)
13087         AND (p_match_option = 'P') THEN
13088       debug_info := '(v_check_line_po_info2 5) Check for Unit of Measure'
13089                     ||' against PO';
13090       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13091           AP_IMPORT_UTILITIES_PKG.Print(
13092             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13093       END IF;
13094       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13095                         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13096                         p_invoice_lines_rec.invoice_line_id,
13097                         'UOM DOES NOT MATCH PO',
13098                         p_default_last_updated_by,
13099                         p_default_last_update_login,
13100                         current_calling_sequence) <> TRUE) THEN
13101         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13102             AP_IMPORT_UTILITIES_PKG.Print(
13103               AP_IMPORT_INVOICES_PKG.g_debug_switch,
13104                  'insert_rejections<-'||current_calling_sequence);
13105         END IF;
13106         RAISE check_po_failure;
13107       END IF;
13108       l_current_invoice_status := 'N';
13109 
13110     END IF;
13111     END IF;  -- Match Basis QUANTITY
13112 
13113     ----------------------------------------------------------------
13114     -- Step 6
13115     -- Check for Valid unit_price, quantity_invoiced and line_amount
13116     -- Amount Based Matching. Nso need to validate line amount based
13117     -- on unit_price and quantity_invoiced, or unit_price based on
13118     -- line_amount and quantity_invoiced, or calculate quantity_inv
13119     -- oiced based on line_amount and unit_price
13120     ----------------------------------------------------------------
13121     IF (p_match_basis = 'QUANTITY') THEN
13122     IF ((p_invoice_lines_rec.quantity_invoiced IS NOT NULL) AND
13123         (p_invoice_lines_rec.unit_price IS NOT NULL) AND
13124         (p_invoice_lines_rec.amount IS NOT NULL)) Then
13125       debug_info := '(v_check_line_po_info2 7) Check for valid unit_price, '
13126                      ||'quantity_invoiced and line_amount';
13127       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13128           AP_IMPORT_UTILITIES_PKG.Print(
13129             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13130       END IF;
13131 
13132       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13133         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13134         'quantity_invoiced = '||to_char(p_invoice_lines_rec.quantity_invoiced)||
13135         ' unit_price = '||to_char(p_invoice_lines_rec.unit_price)||
13136         ' amount = '||to_char(p_invoice_lines_rec.amount));
13137       END IF;
13138 
13139       -- The following can have rounding issues so use line_amount
13140       -- for consistency check.
13141       -- l_calculated_unit_price :=
13142       -- p_invoice_lines_rec.amount / p_quantity_invoiced;
13143       l_calc_line_amount := ap_utilities_pkg.ap_round_currency (
13144         p_invoice_lines_rec.unit_price * p_invoice_lines_rec.quantity_invoiced,
13145         p_invoice_rec.invoice_currency_code);
13146       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13147         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13148         '------------------>
13149         l_calc_line_amount = '||to_char(l_calc_line_amount));
13150       END IF;
13151 
13152       -- Bug 5469166. Added the g_source <> 'PPA' condition
13153 
13154       IF (l_calc_line_amount <> p_invoice_lines_rec.amount) OR
13155 /*
13156 2830338 : Raise INVALID PRICE/QUANTITY if Amount does not have the
13157                   same sign as Quantity
13158 */
13159       --Bug6836072
13160         ((SIGN(p_invoice_lines_rec.amount) <> SIGN(p_invoice_lines_rec.quantity_invoiced)
13161          AND
13162          (NVL(p_invoice_lines_rec.amount, 0) <> 0))
13163         AND AP_IMPORT_INVOICES_PKG.g_source <> 'PPA')
13164         THEN
13165         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13166                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13167                         p_invoice_lines_rec.invoice_line_id,
13168                         'INVALID PRICE/QUANTITY/AMOUNT',
13169                         p_default_last_updated_by,
13170                         p_default_last_update_login,
13171                         current_calling_sequence,
13172                         'Y',
13173                         'QUANTITY INVOICED',
13174                         p_invoice_lines_rec.quantity_invoiced,
13175                         'UNIT PRICE',
13176                         p_invoice_lines_rec.unit_price,
13177                         'INVOICE LINE AMOUNT',
13178                         p_invoice_lines_rec.amount) <> TRUE) THEN
13179           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13180               AP_IMPORT_UTILITIES_PKG.Print(
13181                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
13182                   'insert_rejections<-'||current_calling_sequence);
13183           END IF;
13184           RAISE check_po_failure;
13185         END IF;
13186         l_current_invoice_status := 'N';
13187       END IF;
13188     ELSIF ((p_invoice_lines_rec.quantity_invoiced IS NOT NULL) AND
13189            (P_INVOICE_LINES_REC.UNIT_PRICE IS NULL) AND
13190            (p_invoice_lines_rec.amount IS NOT NULL)) Then
13191       debug_info := '(v_check_line_po_info2 7) Get unit_price from '
13192                     ||'quantity_invoiced and line_amount';
13193       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13194         AP_IMPORT_UTILITIES_PKG.Print(
13195           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13196       END IF;
13197       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13198         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13199         'inside the else condition ');
13200       END IF;
13201 
13202 /*
13203 2830338 : Raise INVALID PRICE/QUANTITY if Amount does not have the
13204                   same sign as Quantity
13205 */
13206       --Bug6836072
13207       IF ((NVL(p_invoice_lines_rec.amount, 0) <> 0)
13208           AND SIGN(p_invoice_lines_rec.amount) <> SIGN(p_invoice_lines_rec.quantity_invoiced))
13209       THEN
13210          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13211                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13212                         p_invoice_lines_rec.invoice_line_id,
13213                         'INVALID PRICE/QUANTITY/AMOUNT',
13214                         p_default_last_updated_by,
13215                         p_default_last_update_login,
13216                         current_calling_sequence,
13217                         'Y',
13218                         'QUANTITY INVOICED',
13219                         p_invoice_lines_rec.quantity_invoiced,
13220                         'UNIT PRICE',
13221                         p_invoice_lines_rec.unit_price,
13222                         'INVOICE LINE AMOUNT',
13223                         p_invoice_lines_rec.amount) <> TRUE) THEN
13224          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13225               AP_IMPORT_UTILITIES_PKG.Print(
13226                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
13227                   'insert_rejections<-'||current_calling_sequence);
13228           END IF;
13229           RAISE check_po_failure;
13230         END IF;
13231         l_current_invoice_status := 'N';
13232       END IF;
13233 
13234       -- We should calc the unit price instead of using the one from PO
13235       -- Use from PO only if both p_unit_price and p_quantity_invoiced are null
13236       /*Bug 5495483 Added the below IF condition*/
13237       /*l_unit_price := p_invoice_lines_rec.amount /
13238                     p_invoice_lines_rec.quantity_invoiced;*/
13239       IF (p_invoice_lines_rec.quantity_invoiced=0) THEN
13240             l_unit_price :=0;
13241       ELSE
13242             l_unit_price := p_invoice_lines_rec.amount /p_invoice_lines_rec.quantity_invoiced;
13243       END IF;
13244 
13245       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13246           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13247           '------------------>
13248           l_unit_price = '||to_char(l_unit_price));
13249       END IF;
13250 
13251     END IF;
13252 
13253   -- Calculate qty invoiced.
13254   -- Retropricing: Qnantity_invoiced will not be calculated
13255   -- for PPA Lines
13256 
13257     IF (p_invoice_lines_rec.quantity_invoiced IS NULL) Then
13258       -- Quantity is not being rounded
13259       l_dec_unit_price := nvl(l_unit_price,nvl(l_po_unit_price,1));
13260 
13261       IF (l_dec_unit_price = 0) Then
13262          l_quantity_invoiced := p_invoice_lines_rec.amount;
13263       ELSE
13264          l_quantity_invoiced := ROUND(p_invoice_lines_rec.amount/l_dec_unit_price,15) ;
13265       END IF;
13266 
13267       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13268         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13269              '------------------>
13270           l_quantity_invoiced = '||to_char(l_quantity_invoiced)
13271       ||' line_amount = '||to_char(p_invoice_lines_rec.amount)
13272       ||' unit_price = '||to_char(l_unit_price));
13273       END IF;
13274 
13275     END IF;
13276 
13277     END IF; -- Match Basis QUANTITY
13278 
13279     ------------------------------------------------------------
13280     -- Step 7
13281     -- Calculate line_amount if unit_price and quantiy_invoiced
13282     -- are provided in case of Amount Based Matching
13283     ------------------------------------------------------------
13284     IF (p_match_basis = 'AMOUNT' AND
13285         p_invoice_lines_rec.amount IS NULL) THEN
13286       IF ((p_invoice_lines_rec.quantity_invoiced IS NOT NULL) AND
13287         (p_invoice_lines_rec.unit_price IS NOT NULL)) THEN
13288         debug_info := '(v_check_line_po_info2 7) Calculate line_amount, '
13289                      ||'in case of match basis is AMOUNT';
13290         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13291           AP_IMPORT_UTILITIES_PKG.Print(
13292             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13293         END IF;
13294 
13295         -- The following can have rounding issues so use line_amount
13296         -- for consistency check.
13297         -- l_calculated_unit_price :=
13298         -- p_invoice_lines_rec.amount / p_quantity_invoiced;
13299         l_calc_line_amount := ap_utilities_pkg.ap_round_currency (
13300           p_invoice_lines_rec.unit_price * p_invoice_lines_rec.quantity_invoiced,
13301           p_invoice_rec.invoice_currency_code);
13302         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13303           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13304           '------------------>
13305           l_calc_line_amount = '||to_char(l_calc_line_amount));
13306         END IF;
13307       ELSE
13308         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13309                        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13310                         p_invoice_lines_rec.invoice_line_id,
13311                         'INSUFFICIENT AMOUNT INFO',
13312                         p_default_last_updated_by,
13313                         p_default_last_update_login,
13314                         current_calling_sequence,
13315                         'Y',
13316                         'QUANTITY INVOICED',
13317                         p_invoice_lines_rec.quantity_invoiced,
13318                         'UNIT PRICE',
13319                         p_invoice_lines_rec.unit_price,
13320                         'INVOICE LINE AMOUNT',
13321                         p_invoice_lines_rec.amount) <> TRUE) THEN
13322           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13323               AP_IMPORT_UTILITIES_PKG.Print(
13324                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
13325                   'insert_rejections<-'||current_calling_sequence);
13326           END IF;
13327           RAISE check_po_failure;
13328         END IF;
13329         l_current_invoice_status := 'N';
13330       END IF;
13331     END IF;
13332 
13333     -------------------------------------------------------------
13334     -- Step 8
13335     -- Check for Invalid Unit Price against PO
13336     -- Retropricing:
13337     -- We assume that PO will not allow to retroprice a PO again
13338     -- if there are pending PO shipment instructions in the
13339     -- AP_INVOICE_LINES_INTERFACE. If the PO's unit price is not
13340     -- equal to the unit price on the PPA, then it should
13341     -- be rejected . Currently UNIT PRC NOT EQUAL TO PO
13342     -- rejection is only meant for EDI-GATEWAY.
13343     -- Thia step should not be executed in context of PPA's.
13344     -- Amount Based Matching. Reject for negative total amount
13345     -- invoiced against given PO
13346     -------------------------------------------------------------
13347     IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
13348         --
13349         IF (l_po_line_location_id IS NOT NULL) THEN
13350           l_qty_invoiced := nvl(p_invoice_lines_rec.quantity_invoiced,
13351                               l_quantity_invoiced);
13352           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13353             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13354               '------------------>
13355               Decoded l_qty_invoiced = '||to_char(l_qty_invoiced));
13356           END IF;
13357           --
13358           -- For Invoice import, we should always average out the price for
13359           -- all matched for a given line_location.
13360           -- This will account for all invoices , credit memos as well as positive
13361           -- price corrections.
13362           --Retropricing: PPA'should be excluded from the quantity_invoiced.
13363 
13364           SELECT NVL(SUM(DECODE(L.MATCH_TYPE,
13365                                 'PRICE_CORRECTION', 0,
13366                                 'PO_PRICE_ADJUSTMENT', 0,
13367                                 'ADJUSTMENT_CORRECTION', 0,
13368                                  NVL(L.quantity_invoiced, 0))),0) +
13369                                  NVL(l_qty_invoiced,0),
13370                                  ROUND(NVL(p_invoice_lines_rec.amount +
13371                                  NVL(SUM(NVL(L.amount, 0)),0),0),5)
13372             INTO l_total_qty_billed,
13373                    l_total_match_amount
13374             FROM ap_invoice_lines L
13375            WHERE l.po_line_location_id = l_po_line_location_id;
13376 
13377           -- If total qty billed is below zero
13378           -- we should reject. In invoice workbench the form takes care of this.
13379           -- Amount Based Matching
13380           IF (l_total_qty_billed < 0 AND
13381              p_match_basis = 'QUANTITY') Then
13382             debug_info := '(v_check_line_po_info2 8) Reject for negative total '
13383                           ||'quantity invoiced against given PO ';
13384             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13385               AP_IMPORT_UTILITIES_PKG.Print(
13386                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13387             END IF;
13388 
13389             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13390                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13391                p_invoice_lines_rec.invoice_line_id,
13392                'NEGATIVE QUANTITY BILLED', --Bug 5134622
13393                p_default_last_updated_by,
13394                p_default_last_update_login,
13395                current_calling_sequence,
13396                'Y',
13397                'QUANTITY INVOICED',
13398                l_total_qty_billed ) <> TRUE) THEN
13399               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13400                  AP_IMPORT_UTILITIES_PKG.Print(
13401                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
13402                    'insert_rejections<-'||current_calling_sequence);
13403               END IF;
13404               RAISE check_po_failure;
13405             END IF;
13406             l_current_invoice_status := 'N';
13407 
13408           END IF; -- total qty billed is less than 0
13409 
13410           -- If total qty billed is zero and total match amount is not equal to zero
13411           -- Case I: total match amount is positive; this will never happen in
13412           -- the above scenario
13413           -- Case II: total match amount is -ve ; essentially we have an extra
13414           -- credit for supplier
13415           -- Discussed with Subir, since the invoice workbench allows this ,
13416           -- we would not reject
13417           IF ((l_total_qty_billed = 0 ) AND
13418               (l_total_match_amount <> 0))Then
13419             debug_info := '(v_check_line_po_info2 9) Extra credit for '||
13420                           'supplier:Negative total match amount against given PO ';
13421             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13422                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13423                                               debug_info);
13424             END IF;
13425 
13426           END IF;
13427 
13428           IF p_invoice_lines_rec.unit_price >
13429              p_positive_price_tolerance * l_po_unit_price THEN
13430               l_positive_price_variance := 1;
13431           ELSE
13432               l_positive_price_variance :=0;
13433           END IF;
13434 
13435           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13436               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13437               '------------------>
13438               l_positive_price_varaince = '||to_char(l_positive_price_variance)
13439           ||' l_total_qty_billed = '||to_char(l_total_qty_billed));
13440           END IF;
13441 
13442           -- Reject even if tolerance is not set
13443           --
13444           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') THEN
13445             IF (l_positive_price_variance > 0) then --modified for 1939078
13446               debug_info := '(v_check_line_po_info2 9) Check for Invalid Unit '
13447                             ||'Price against PO';
13448               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13449                 AP_IMPORT_UTILITIES_PKG.Print(
13450                   AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13451               END IF;
13452 
13453               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13454                            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13455                             p_invoice_lines_rec.invoice_line_id,
13456                             'UNIT PRC NOT EQUAL TO PO',
13457                             p_default_last_updated_by,
13458                             p_default_last_update_login,
13459                             current_calling_sequence) <> TRUE) THEN
13460                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13461                     AP_IMPORT_UTILITIES_PKG.Print(
13462                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
13463                        'insert_rejections<-'||current_calling_sequence);
13464                 END IF;
13465                 RAISE check_po_failure;
13466               END IF;
13467               l_current_invoice_status := 'N';
13468 
13469             END IF; -- l_total_price_variance
13470 
13471           END IF; -- g_source
13472 
13473         ELSIF ((l_po_line_location_id IS NULL) AND
13474                (l_po_line_id IS NOT NULL)) THEN
13475                -- else if po line location is not null
13476           l_qty_invoiced := nvl(p_invoice_lines_rec.quantity_invoiced,
13477                                 l_quantity_invoiced);
13478           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13479               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13480                     '------------------>
13481                 l_qty_invoiced = '||to_char(l_qty_invoiced));
13482           END IF;
13483           --
13484           SELECT  NVL(SUM(DECODE(L.MATCH_TYPE, 'PRICE_CORRECTION', 0,
13485                                  'PO_PRICE_ADJUSTMENT', 0,
13486                                  'ADJUSTMENT_CORRECTION', 0,
13487                                   NVL(L.quantity_invoiced, 0))),0) +
13488                   NVL(l_qty_invoiced,0),
13489                   NVL(SUM(NVL(PLL.amount,0)),0) +
13490                   NVL(p_invoice_lines_rec.amount, l_line_amount)
13491             INTO  l_total_qty_billed,
13492                   l_total_match_amount  /* Amount Based Matching */
13493             FROM  ap_invoice_lines L,
13494                   po_line_locations PLL
13495            WHERE  L.po_line_location_id = PLL.line_location_id
13496              AND  PLL.po_line_id = l_po_line_id;
13497 
13498           -- If total qty billed is below zero
13499           -- we should reject. In invoice workbench the form takes care of this.
13500            -- Amount Based Matching
13501           IF (l_total_qty_billed < 0 AND
13502               p_match_basis = 'QUANTITY') Then
13503               debug_info := '(v_check_line_po_info2 8) Reject for negative total '
13504                  ||'quantity invoiced against given PO(for PO Line match) ';
13505             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13506                 AP_IMPORT_UTILITIES_PKG.Print(
13507                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13508             END IF;
13509 
13510             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13511                      AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13512                      p_invoice_lines_rec.invoice_line_id,
13513                     'NEGATIVE QUANTITY BILLED', --Bug 5134622
13514                      p_default_last_updated_by,
13515                      p_default_last_update_login,
13516                      current_calling_sequence,
13517                      'Y',
13518                      'QUANTITY INVOICED',
13519                      l_total_qty_billed ) <> TRUE) THEN
13520               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13521                 AP_IMPORT_UTILITIES_PKG.Print(
13522                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
13523                  'insert_rejections<-'||current_calling_sequence);
13524               END IF;
13525               RAISE check_po_failure;
13526             END IF;
13527             l_current_invoice_status := 'N';
13528 
13529           /* Amount Based Matching */
13530           -- If total amount is billed zero, We should reject.
13531           -- In Invoice workbench form take care of this
13532           ELSIF (l_total_match_amount < 0 AND
13533                  p_match_basis = 'AMOUNT') Then
13534             debug_info := '(v_check_line_po_info2 8) Reject for negative total '
13535                           ||'amount matched against given PO ';
13536             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13537               AP_IMPORT_UTILITIES_PKG.Print(
13538                 AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13539           END IF;
13540 
13541             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13542                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13543                p_invoice_lines_rec.invoice_line_id,
13544                'INVALID LINE AMOUNT',
13545                p_default_last_updated_by,
13546                p_default_last_update_login,
13547                current_calling_sequence,
13548                'Y',
13549                'AMOUNT INVOICED',
13550                l_total_match_amount ) <> TRUE) THEN
13551               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13552                  AP_IMPORT_UTILITIES_PKG.Print(
13553                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
13554                    'insert_rejections<-'||current_calling_sequence);
13555               END IF;
13556               RAISE check_po_failure;
13557             END IF;
13558             l_current_invoice_status := 'N';
13559 
13560           END IF; -- total qty billed is less than 0
13561 
13562           IF p_invoice_lines_rec.unit_price >
13563              p_positive_price_tolerance * l_po_unit_price THEN
13564               l_positive_price_variance := 1;
13565           ELSE
13566               l_positive_price_variance :=0;
13567           END IF;
13568 
13569           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13570               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13571                 '------------------>
13572                 l_positive_price_variance = '||to_char(l_positive_price_variance)
13573                 ||' l_total_qty_billed = '||to_char(l_total_qty_billed));
13574           END IF;
13575 
13576           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') Then
13577             IF (l_positive_price_variance > 0) THEN --modified for 1939078
13578               debug_info := '(v_check_line_po_info2 9) Check for Invalid Unit  '
13579                             ||'Price against PO';
13580               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13581                 AP_IMPORT_UTILITIES_PKG.Print(
13582                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13583               END IF;
13584 
13585               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13586                           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13587                           p_invoice_lines_rec.invoice_line_id,
13588                           'UNIT PRC NOT EQUAL TO PO',
13589                           p_default_last_updated_by,
13590                           p_default_last_update_login,
13591                           current_calling_sequence) <> TRUE) THEN
13592                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13593                   AP_IMPORT_UTILITIES_PKG.Print(
13594                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
13595                       'insert_rejections<-'||current_calling_sequence);
13596                 END IF;
13597                 RAISE check_po_failure;
13598               END IF;
13599               l_current_invoice_status := 'N';
13600 
13601             END IF; -- l_total_price_variance
13602 
13603           END IF; -- g_source
13604 
13605         END IF; -- po line location id is not null
13606     END IF; -- source <> PPA
13607     ----------------------------------------------------------------
13608     -- Step 10
13609     -- Check for Overbill, if yes then reject. Only if tolerances are set
13610     -- This is as per Aetna's requirement. This can later be implemented
13611     -- as system options. Discussed this with Subir and Lauren 11/5/97
13612     -- Even here we assume zero for null quantity ordered tolerance
13613     -- Only for EDI GATEWAY source 5/4/98
13614     -- Retropricing:
13615     -- Overbill rejection is meant only for EDI Gateway. The following
13616     -- code should not reject PPA Invoice Lines. Adding the IF condition
13617     -- so that the code is not executed for PPA's.
13618     -----------------------------------------------------------------
13619     IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
13620 
13621        IF (l_po_line_location_id IS NOT NULL) THEN
13622           debug_info := '(v_check_line_po_info2 10) Check for quantity overbill '
13623                         ||'for PO Shipment';
13624 
13625           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13626               AP_IMPORT_UTILITIES_PKG.Print(
13627                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13628           END IF;
13629 
13630           IF (AP_IMPORT_UTILITIES_PKG.get_overbill_for_shipment(
13631                 l_po_line_location_id,              -- IN
13632                 NVL(p_invoice_lines_rec.quantity_invoiced,
13633                 l_quantity_invoiced),               -- IN
13634 		p_invoice_lines_rec.amount,         --IN
13635                 l_overbill,                         -- OUT NOCOPY
13636                 l_quantity_outstanding,             -- OUT NOCOPY
13637                 l_quantity_ordered,                 -- OUT NOCOPY
13638                 l_qty_already_billed,               -- OUT NOCOPY
13639 		l_amount_outstanding,		    -- OUT NOCOPY
13640 		l_amount_ordered,		    -- OUT NOCOPY
13641 		l_amt_already_billed,		    -- OUT NOCOPY
13642                 current_calling_sequence) <> TRUE) THEN
13643 
13644             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13645                 AP_IMPORT_UTILITIES_PKG.Print(
13646                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
13647                     'get_overbill_for_shipment<-'||current_calling_sequence);
13648             END IF;
13649             RAISE check_po_failure;
13650           END IF;
13651 
13652           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13653               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13654                '------------------> l_overbill = '||l_overbill
13655             ||' l_quantity_outstanding = ' ||to_char(l_quantity_outstanding)
13656             ||' l_quantity_ordered =  '    ||to_char(l_quantity_ordered)
13657             ||' l_qty_already_billed =  '  ||to_char(l_qty_already_billed)
13658 	    ||' l_amount_outstanding = '   ||to_char(l_amount_outstanding)
13659 	    ||' l_amount_ordered =  '      ||to_char(l_amount_ordered)
13660 	    ||' l_amt_already_billed =  '  ||to_char(l_amt_already_billed)
13661             ||' p_max_qty_ord_tolerance = '||to_char(p_max_qty_ord_tolerance)
13662 	    ||' p_max_amt_ord_tolerance = '||to_char(p_max_amt_ord_tolerance)
13663             ||' p_qty_ord_tolerance  = '   ||to_char(p_qty_ord_tolerance)
13664 	    ||' p_amt_ord_tolerance  = '   ||to_char(p_amt_ord_tolerance));
13665 
13666           END IF;
13667 
13668           -- This is as per EDI requirements. We might need to address this later
13669           -- with quick invoices.
13670 
13671           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') Then
13672 
13673             IF(p_match_basis = 'QUANTITY') THEN
13674 
13675               IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
13676                        l_qty_already_billed) >
13677                     (NVL(p_qty_ord_tolerance,1) * l_quantity_ordered)) THEN
13678                  debug_info := '(v_check_line_po_info2 11) Reject for '
13679                             ||'p_qty_ord_tolerance';
13680                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13681                     AP_IMPORT_UTILITIES_PKG.Print(
13682                        AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13683                  END IF;
13684 
13685                  l_qty_based_rejection := 'Y';
13686 
13687               END IF;
13688 
13689               IF (p_max_qty_ord_tolerance IS NOT NULL) Then
13690 
13691                  IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
13692                        l_qty_already_billed) >
13693                       (p_max_qty_ord_tolerance + l_quantity_ordered)) THEN
13694                     debug_info := '(v_check_line_po_info2 12) Reject for '
13695                                ||'p_max_qty_ord_tolerance';
13696                     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13697                       AP_IMPORT_UTILITIES_PKG.Print(
13698                          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13699                     END IF;
13700                     l_qty_based_rejection := 'Y';
13701 
13702                  END IF;
13703 
13704               END IF;
13705 
13706               IF (nvl(l_qty_based_rejection,'N') = 'Y') Then
13707                  debug_info := '(v_check_line_po_info2 13) Reject for Quantity '
13708                             ||'overbill for PO Shipment';
13709                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13710                       AP_IMPORT_UTILITIES_PKG.Print(
13711                  	     AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13712                  END IF;
13713 
13714                  IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13715                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13716                             p_invoice_lines_rec.invoice_line_id,
13717                             'INVALID INVOICE QUANTITY',
13718                             p_default_last_updated_by,
13719                             p_default_last_update_login,
13720                             current_calling_sequence) <> TRUE) THEN
13721 
13722                       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13723                          AP_IMPORT_UTILITIES_PKG.Print(
13724                             AP_IMPORT_INVOICES_PKG.g_debug_switch,
13725                                'insert_rejections<-'||current_calling_sequence);
13726                       END IF;
13727 
13728                       RAISE check_po_failure;
13729                   END IF;
13730                   l_current_invoice_status := 'N';
13731 
13732                END IF; -- l_qty_based_rejection = 'Y'
13733 
13734 	   ELSIF (p_match_basis = 'AMOUNT') THEN
13735 
13736 	       IF ((p_invoice_lines_rec.amount + l_amt_already_billed) >
13737                    (NVL(p_amt_ord_tolerance,1) * l_amount_ordered)) THEN
13738 
13739                  debug_info := '(v_check_line_po_info2 14) Reject for '
13740                             ||'p_amt_ord_tolerance';
13741                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13742                      AP_IMPORT_UTILITIES_PKG.Print(
13743                        AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13744                  END IF;
13745 
13746                  l_amt_based_rejection := 'Y';
13747 
13748                END IF;
13749 
13750                IF (p_max_amt_ord_tolerance IS NOT NULL) Then
13751 
13752                   IF ((p_invoice_lines_rec.amount + l_amt_already_billed) >
13753                       (p_max_amt_ord_tolerance + l_amount_ordered)) THEN
13754 
13755                       debug_info := '(v_check_line_po_info2 15) Reject for '
13756                                ||'p_max_amt_ord_tolerance';
13757                       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13758                          AP_IMPORT_UTILITIES_PKG.Print(
13759                             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13760                       END IF;
13761                       l_amt_based_rejection := 'Y';
13762 
13763                   END IF;
13764 
13765                END IF;
13766 
13767                IF (nvl(l_amt_based_rejection,'N') = 'Y') Then
13768 
13769                   debug_info := '(v_check_line_po_info2 16) Reject for Amount '
13770                             ||'overbill for PO Shipment';
13771                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13772                       AP_IMPORT_UTILITIES_PKG.Print(
13773                           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13774                   END IF;
13775 
13776                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13777                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13778                             p_invoice_lines_rec.invoice_line_id,
13779                             'LINE AMOUNT EXCEEDED TOLERANCE',
13780                             p_default_last_updated_by,
13781                             p_default_last_update_login,
13782                             current_calling_sequence) <> TRUE) THEN
13783 
13784                       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13785                            AP_IMPORT_UTILITIES_PKG.Print(
13786                                AP_IMPORT_INVOICES_PKG.g_debug_switch,
13787                                'insert_rejections<-'||current_calling_sequence);
13788                       END IF;
13789 
13790                       RAISE check_po_failure;
13791                   END IF;
13792 
13793                   l_current_invoice_status := 'N';
13794 
13795                END IF; -- nvl(l_amt_based_rejection,'N') = 'Y'
13796 
13797             END IF; --p_match_basis = 'QUANTITY'
13798 
13799           END IF; -- g_source = 'EDI GATEWAY'
13800 
13801        ELSIF ((l_po_line_location_id IS NULL)AND
13802                (l_po_line_id IS NOT NULL)) THEN
13803           -- po line location id is not null
13804           debug_info := '(v_check_line_po_info2 17) Check for quantity overbill '
13805                         ||'for PO Line';
13806           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
13807             AP_IMPORT_UTILITIES_PKG.Print(
13808               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13809           END IF;
13810 
13811           IF (AP_IMPORT_UTILITIES_PKG.get_overbill_for_po_line(
13812               l_po_line_id,
13813               NVL(p_invoice_lines_rec.quantity_invoiced, l_quantity_invoiced),
13814 	      p_invoice_lines_rec.amount,  --IN
13815               l_overbill,                  -- OUT
13816               l_outstanding,     	   -- OUT
13817               l_ordered,         	   -- OUT
13818               l_already_billed,            -- OUT
13819 	      l_po_line_matching_basis,    -- OUT
13820               current_calling_sequence) <> TRUE) THEN
13821 
13822               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13823                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13824                    'get_overbill_for_po_line<-'||current_calling_sequence);
13825               END IF;
13826               RAISE check_po_failure;
13827           END IF;
13828 
13829           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13830             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
13831                '------------------> l_overbill = '||l_overbill
13832                ||' l_outstanding quantity/amount = '||to_char(l_outstanding)
13833               ||' l_ordered quantity/amount = '||to_char(l_ordered)
13834               ||' l_already_billed quantity/amount = '||to_char(l_already_billed)
13835               ||' p_max_qty_ord_tolerance  = '||to_char(p_max_qty_ord_tolerance)
13836 	      ||' p_max_amt_ord_tolerance = '||to_char(p_max_amt_ord_tolerance)
13837               ||' p_qty_ord_tolerance  = '||to_char(p_qty_ord_tolerance)
13838 	      ||' p_amt_ord_tolerance  = '||to_char(p_amt_ord_tolerance));
13839 
13840           END IF;
13841 
13842           -- This is as per EDI requirements. We might need to address this later
13843           -- with quick invoices.
13844           IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') Then
13845 
13846 	     IF (l_po_line_matching_basis = 'QUANTITY') THEN
13847 
13848                 IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
13849                	         l_already_billed) >
13850                     (NVL(p_qty_ord_tolerance,1) * l_ordered)) THEN
13851                      debug_info := '(v_check_line_po_info2 18) Reject for '
13852                             ||'p_qty_ord_tolerance';
13853                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13854                       AP_IMPORT_UTILITIES_PKG.Print(
13855                           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13856                    END IF;
13857                    l_qty_based_rejection := 'Y';
13858                 END IF;
13859 
13860                 IF (p_max_qty_ord_tolerance IS NOT NULL) Then
13861                    IF ((NVL(p_invoice_lines_rec.quantity_invoiced,l_quantity_invoiced) +
13862                           l_already_billed) >
13863                        (p_max_qty_ord_tolerance + l_ordered)) THEN
13864 
13865                        debug_info := '(v_check_line_po_info2 19) Reject for '
13866                               ||'p_max_qty_ord_tolerance';
13867                         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13868                   	   AP_IMPORT_UTILITIES_PKG.Print(
13869                     		AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13870                 	END IF;
13871                 	l_qty_based_rejection := 'Y';
13872                    END IF;
13873                 END IF;
13874 
13875                 IF (nvl(l_qty_based_rejection,'N') = 'Y') THEN
13876                    debug_info := '(v_check_line_po_info2 20) Reject for Quantity '
13877                              ||'overbill for PO Line';
13878                    IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13879                 	AP_IMPORT_UTILITIES_PKG.Print(
13880                   		AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13881               	   END IF;
13882 
13883               	   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13884                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13885                             p_invoice_lines_rec.invoice_line_id,
13886                             'INVALID INVOICE QUANTITY',
13887                             p_default_last_updated_by,
13888                             p_default_last_update_login,
13889                             current_calling_sequence) <> TRUE) THEN
13890                         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13891                   	   AP_IMPORT_UTILITIES_PKG.Print(
13892                     		AP_IMPORT_INVOICES_PKG.g_debug_switch,
13893                       		'insert_rejections<-'||current_calling_sequence);
13894                 	END IF;
13895                 	RAISE check_po_failure;
13896               	   END IF;
13897 
13898                    l_current_invoice_status := 'N';
13899 
13900                 END IF; /* nvl(l_qty_based_rejection,'N') = 'Y' */
13901 
13902             ELSIF (l_po_line_matching_basis = 'AMOUNT') THEN
13903 
13904                IF ((p_invoice_lines_rec.amount + l_already_billed) >
13905                   (NVL(p_amt_ord_tolerance,1) * l_ordered)) THEN
13906                   debug_info := '(v_check_line_po_info2 21) Reject for '
13907                                  ||'p_amt_ord_tolerance';
13908 
13909                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13910                      AP_IMPORT_UTILITIES_PKG.Print(
13911                        AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
13912                   END IF;
13913                   l_amt_based_rejection := 'Y';
13914 
13915                END IF;
13916 
13917                IF (p_max_amt_ord_tolerance IS NOT NULL) Then
13918 
13919                   IF ((p_invoice_lines_rec.amount + l_already_billed) >
13920                      (p_max_amt_ord_tolerance + l_ordered)) THEN
13921 
13922                      debug_info := '(v_check_line_po_info2 22) Reject for '
13923                                   ||'p_max_amt_ord_tolerance';
13924                      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13925                         AP_IMPORT_UTILITIES_PKG.Print(
13926                           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13927                      END IF;
13928 
13929                      l_amt_based_rejection := 'Y';
13930 
13931                   END IF;
13932 
13933                END IF;
13934 
13935                IF (nvl(l_amt_based_rejection,'N') = 'Y') THEN
13936                   debug_info := '(v_check_line_po_info2 23) Reject for Amount '
13937                                ||'overbill for PO Line';
13938                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13939                     AP_IMPORT_UTILITIES_PKG.Print(
13940                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13941                   END IF;
13942 
13943                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
13944                             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
13945                             p_invoice_lines_rec.invoice_line_id,
13946                             'LINE AMOUNT EXCEEDED TOLERANCE',
13947                             p_default_last_updated_by,
13948                             p_default_last_update_login,
13949                             current_calling_sequence) <> TRUE) THEN
13950                      IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13951                        AP_IMPORT_UTILITIES_PKG.Print(
13952                            AP_IMPORT_INVOICES_PKG.g_debug_switch,
13953                            'insert_rejections<-'||current_calling_sequence);
13954                      END IF;
13955                      RAISE check_po_failure;
13956                   END IF;
13957 
13958                   l_current_invoice_status := 'N';
13959 
13960                END IF;
13961 
13962 	    END IF; --l_po_line_matching_basis = 'QUANTITY'
13963 
13964           END IF ; --g_source = 'EDI'...
13965 
13966    --     END IF; -- overbill
13967 
13968       END IF; -- l_po_header_id is NOT NULL
13969 
13970   END IF; --source <> PPA
13971 
13972   p_current_invoice_status := l_current_invoice_status;
13973   p_calc_quantity_invoiced := l_quantity_invoiced;
13974   p_calc_unit_price        := l_dec_unit_price;
13975 
13976   RETURN(TRUE);
13977 
13978 EXCEPTION
13979   WHEN OTHERS THEN
13980     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13981       AP_IMPORT_UTILITIES_PKG.Print(
13982         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
13983     END IF;
13984 
13985     IF (SQLCODE < 0) then
13986       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
13987         AP_IMPORT_UTILITIES_PKG.Print(
13988           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
13989       END IF;
13990     END IF;
13991     RETURN(FALSE);
13992 
13993 END v_check_line_po_info2;
13994 
13995 FUNCTION v_check_po_overlay (
13996    p_invoice_rec	       IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
13997    p_invoice_lines_rec         IN  AP_IMPORT_INVOICES_PKG.r_line_info_rec,
13998    p_po_line_id                IN            NUMBER,
13999    p_po_line_location_id       IN            NUMBER,
14000    p_po_distribution_id        IN            NUMBER,
14001    p_set_of_books_id           IN            NUMBER,
14002    p_default_last_updated_by   IN            NUMBER,
14003    p_default_last_update_login IN            NUMBER,
14004    p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
14005    p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
14006 IS
14007    check_po_failure              EXCEPTION;
14008    l_po_line_id                NUMBER    := p_po_line_id;
14009    l_po_line_location_id    NUMBER    := p_po_line_location_id;
14010    l_po_distribution_id        NUMBER    := p_po_distribution_id;
14011    l_unbuilt_flex           VARCHAR2(240):='';
14012    l_reason_unbuilt_flex    VARCHAR2(2000):='';
14013    l_code_combination_id    NUMBER;
14014    l_current_invoice_status    VARCHAR2(1) := p_current_invoice_status;
14015    l_dist_code_concatenated    VARCHAR2(2000):='';
14016    current_calling_sequence VARCHAR2(2000);
14017    debug_info               VARCHAR2(500);
14018 
14019 CURSOR    po_distributions_cur IS
14020    SELECT code_combination_id
14021      FROM po_distributions
14022     WHERE line_location_id = l_po_line_location_id
14023     AND nvl(accrue_on_receipt_flag,'N') <> 'Y' --Bug 2667171 added this Condition
14024     ORDER BY distribution_num;
14025 
14026 --Contract Payments: Modified the where clause
14027 CURSOR    po_line_locations_cur IS
14028    SELECT pd.code_combination_id
14029      FROM po_distributions pd,
14030       po_line_locations pll
14031     WHERE pd.line_location_id = pll.line_location_id
14032       AND pll.po_line_id = l_po_line_id
14033       AND(
14034           (p_invoice_rec.invoice_type_lookup_code <> 'PREPAYMENT' and
14035            pll.SHIPMENT_TYPE IN ('STANDARD','BLANKET','SCHEDULED')
14036           ) OR
14037           (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' and
14038            ((pll.payment_type IS NOT NULL and pll.shipment_type = 'PREPAYMENT') or
14039             (pll.payment_type IS NULL and pll.shipment_type IN ('STANDARD','BLANKET','SCHEDULED'))
14040            )
14041           )
14042          )
14043       AND pll.APPROVED_FLAG = 'Y'
14044     ORDER BY pll.shipment_num,pd.distribution_num;
14045 
14046 BEGIN
14047   -- Update the calling sequence
14048   --
14049   current_calling_sequence :=  'v_check_po_overlay<-'||P_calling_sequence;
14050 
14051   ----------------------------------------------------------
14052   -- Check Account Overlay
14053   -- Step 1
14054   ----------------------------------------------------------
14055   IF ((l_current_invoice_status <> 'N') AND
14056       ((p_invoice_lines_rec.dist_code_concatenated IS NOT NULL) OR
14057        (p_invoice_lines_rec.balancing_segment IS NOT NULL) OR
14058        (p_invoice_lines_rec.cost_center_segment IS NOT NULL) OR
14059        (p_invoice_lines_rec.account_segment IS NOT NULL)) ) THEN
14060     IF (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL) THEN
14061       l_dist_code_concatenated := p_invoice_lines_rec.dist_code_concatenated;
14062     END IF;
14063 
14064     IF (l_po_distribution_id IS NOT NULL) THEN
14065       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14066         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14067            '(v_check_po_overlay 1) Get l_code_combination_id FROM '
14068            ||'l_po_distribution_id ');
14069       END IF;
14070 
14071       SELECT code_combination_id
14072         INTO l_code_combination_id
14073         FROM po_distributions
14074        WHERE po_distribution_id = l_po_distribution_id
14075          AND line_location_id IS NOT NULL; /* BUG 3253594 */
14076       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14077         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14078           '------------------> l_code_combination_id  = '
14079           || to_char(l_code_combination_id)
14080           ||'balancing_segment ='||p_invoice_lines_rec.balancing_segment
14081           ||'cost_center_segment ='||p_invoice_lines_rec.cost_center_segment
14082           ||'account_segment ='||p_invoice_lines_rec.account_segment
14083           ||'dist_code_concatenated ='
14084           ||p_invoice_lines_rec.dist_code_concatenated);
14085         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14086         '(v_check_po_overlay 2) Check Overlay Segments fOR '
14087         ||'l_po_distribution_id ');
14088       END IF;
14089 
14090       IF (AP_UTILITIES_PKG.overlay_segments(
14091            p_invoice_lines_rec.balancing_segment,
14092            p_invoice_lines_rec.cost_center_segment,
14093            p_invoice_lines_rec.account_segment,
14094            l_dist_code_concatenated,
14095            l_code_combination_id , -- OUT NOCOPY
14096            p_set_of_books_id ,
14097            'CHECK' , -- Overlay Mode
14098            l_unbuilt_flex , -- OUT NOCOPY
14099            l_reason_unbuilt_flex , -- OUT NOCOPY
14100            FND_GLOBAL.RESP_APPL_ID,
14101            FND_GLOBAL.RESP_ID,
14102            FND_GLOBAL.USER_ID,
14103            current_calling_sequence ,
14104        NULL) <> TRUE) THEN
14105         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14106           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14107             '(v_check_po_overlay 2) Overlay_Segments<-'
14108              ||current_calling_sequence);
14109         END IF;
14110         Raise check_po_failure;
14111       ELSE
14112         -- show output values (only IF debug_switch = 'Y')
14113         --
14114         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14115           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14116             '------------------> l_unbuilt_flex = '|| l_unbuilt_flex
14117             ||'l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
14118             ||'l_code_combination_id = '|| to_char(l_code_combination_id));
14119         END IF;
14120 
14121         IF (l_code_combination_id = -1) THEN
14122           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14123             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14124               '(v_check_po_overlay 3) Invalid code_combination_id overlay');
14125           END IF;
14126 
14127           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14128             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14129                p_invoice_lines_rec.invoice_line_id,
14130                'INVALID ACCT OVERLAY',
14131                p_default_last_updated_by,
14132                p_default_last_update_login,
14133                current_calling_sequence) <> TRUE) THEN
14134           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14135             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14136               'insert_rejections<-'||current_calling_sequence);
14137           END IF;
14138           RAISE check_po_failure;
14139         END IF; -- Code combination id is -1
14140         l_current_invoice_status := 'N';
14141         END IF; -- added by iyas for code_combination_id
14142       END IF; -- IF overlay segments is other than TRUE
14143     ELSIF (l_po_line_location_id IS NOT NULL) THEN
14144       -- IF po distribution id is not NULL
14145       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14146         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14147           '(v_check_po_overlay 1) Get l_code_combination_id FROM '
14148           ||'l_po_line_location_id ');
14149         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14150           '(v_check_po_overlay 1) Open po_distributions ');
14151       END IF;
14152 
14153       OPEN po_distributions_cur;
14154 
14155       LOOP
14156       --
14157       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14158         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14159              '(v_check_po_overlay 2) Fetch po_distributions_cur ');
14160       END IF;
14161 
14162       FETCH po_distributions_cur  INTO
14163                 l_code_combination_id;
14164       --
14165       EXIT WHEN po_distributions_cur%NOTFOUND OR
14166                 po_distributions_cur%NOTFOUND IS NULL;
14167 
14168       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14169         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14170             '------------------> l_code_combination_id  = '
14171          || to_char(l_code_combination_id)
14172          ||'balancing_segment ='||p_invoice_lines_rec.balancing_segment
14173          ||'cost_center_segment ='||p_invoice_lines_rec.cost_center_segment
14174          ||'account_segment ='||p_invoice_lines_rec.account_segment
14175          ||'l_dist_code_concatenated ='||l_dist_code_concatenated);
14176 
14177         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14178           '(v_check_po_overlay 3) Check Overlay Segments fOR '
14179           ||'l_po_line_location_id ');
14180       END IF;
14181 
14182       IF (AP_UTILITIES_PKG.overlay_segments(
14183              p_invoice_lines_rec.balancing_segment,
14184              p_invoice_lines_rec.cost_center_segment,
14185              p_invoice_lines_rec.account_segment,
14186              l_dist_code_concatenated,
14187              l_code_combination_id ,         -- OUT NOCOPY
14188              p_set_of_books_id ,
14189              'CHECK' ,                 -- Overlay Mode
14190              l_unbuilt_flex ,             -- OUT NOCOPY
14191              l_reason_unbuilt_flex ,         -- OUT NOCOPY
14192              FND_GLOBAL.RESP_APPL_ID,
14193              FND_GLOBAL.RESP_ID,
14194              FND_GLOBAL.USER_ID,
14195              current_calling_sequence,
14196              NULL ) <> TRUE) THEN
14197         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14198           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14199             '(v_check_po_overlay 3) Overlay_Segments<-'
14200              ||current_calling_sequence);
14201         END IF;
14202         CLOSE po_distributions_cur;
14203         RAISE check_po_failure;
14204       ELSE
14205         -- show output values (only IF debug_switch = 'Y')
14206         --
14207         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14208           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14209             '------------------> l_unbuilt_flex = '||l_unbuilt_flex
14210             ||'l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
14211             ||'l_code_combination_id = '|| to_char(l_code_combination_id));
14212         END IF;
14213 
14214         IF (l_code_combination_id = -1) THEN
14215           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14216             AP_IMPORT_UTILITIES_PKG.Print(
14217              AP_IMPORT_INVOICES_PKG.g_debug_switch,
14218              '(v_check_po_overlay 4) Invalid code_combination_id overlay');
14219           END IF;
14220 
14221           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14222              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14223              p_invoice_lines_rec.invoice_line_id,
14224              'INVALID ACCT OVERLAY',
14225              p_default_last_updated_by,
14226              p_default_last_update_login,
14227              current_calling_sequence) <> TRUE) THEN
14228           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14229               AP_IMPORT_UTILITIES_PKG.Print(
14230                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
14231                   'insert_rejections<-'||current_calling_sequence);
14232           END IF;
14233           CLOSE po_distributions_cur;
14234           RAISE check_po_failure;
14235             --
14236           END IF;
14237           l_current_invoice_status := 'N';
14238         END IF; -- code combination id is -1
14239       END IF; --overlay segments
14240 
14241       END LOOP;
14242       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14243         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14244           '(v_check_po_overlay 5) Close po_distributions ');
14245       END IF;
14246       CLOSE po_distributions_cur;
14247     ELSIF ((l_po_line_id IS NOT NULL) AND
14248            (l_po_line_location_id IS NULL)) THEN
14249          -- po distribution id is not NULL
14250       -- PO Line Level Matching
14251       --
14252       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14253         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14254           '(v_check_po_overlay 1) Get l_code_combination_id FROM l_po_line_id ');
14255         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14256           '(v_check_po_overlay 1) Open po_line_locations ');
14257       END IF;
14258 
14259       OPEN po_line_locations_cur;
14260 
14261       LOOP
14262       --
14263       --
14264       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14265         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14266           '(v_check_po_overlay 2) Fetch po_line_locations_cur ');
14267       END IF;
14268 
14269       FETCH po_line_locations_cur  INTO l_code_combination_id;
14270       --
14271       EXIT WHEN po_line_locations_cur%NOTFOUND OR
14272                 po_line_locations_cur%NOTFOUND IS NULL;
14273 
14274       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14275         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14276           '------------------> l_code_combination_id  = '||
14277           to_char(l_code_combination_id)
14278           ||'balancing_segment ='||p_invoice_lines_rec.balancing_segment
14279           ||'cost_center_segment ='||p_invoice_lines_rec.cost_center_segment
14280           ||'account_segment ='||p_invoice_lines_rec.account_segment
14281           ||'l_dist_code_concatenated ='||l_dist_code_concatenated);
14282         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14283           '(v_check_po_overlay 3) Check Overlay Segments fOR l_po_line_id ');
14284       END IF;
14285 
14286       IF (AP_UTILITIES_PKG.overlay_segments(
14287           p_invoice_lines_rec.balancing_segment,
14288           p_invoice_lines_rec.cost_center_segment,
14289           p_invoice_lines_rec.account_segment,
14290           l_dist_code_concatenated,
14291           l_code_combination_id,             -- OUT NOCOPY
14292           p_set_of_books_id,
14293           'CHECK' ,                 -- Overlay Mode
14294           l_unbuilt_flex ,                 -- OUT NOCOPY
14295           l_reason_unbuilt_flex ,             -- OUT NOCOPY
14296           FND_GLOBAL.RESP_APPL_ID,
14297           FND_GLOBAL.RESP_ID,
14298           FND_GLOBAL.USER_ID,
14299           current_calling_sequence ,
14300       NULL) <> TRUE) THEN
14301         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14302           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14303             '(v_check_po_overlay 3) Overlay_Segments<-'
14304             ||current_calling_sequence);
14305         END IF;
14306         CLOSE po_line_locations_cur;
14307         Raise check_po_failure;
14308       ELSE
14309         -- show output values (only IF debug_switch = 'Y')
14310         --
14311         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14312           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14313              '------------------>
14314            l_unbuilt_flex = '||l_unbuilt_flex
14315              ||'l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
14316              ||'l_code_combination_id = '|| to_char(l_code_combination_id));
14317         END IF;
14318         IF (l_code_combination_id = -1) THEN
14319           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14320             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14321               '(v_check_po_overlay 4) Invalid code_combination_id overlay');
14322           END IF;
14323           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14324              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14325                 p_invoice_lines_rec.invoice_line_id,
14326                 'INVALID ACCT OVERLAY',
14327                 p_default_last_updated_by,
14328                 p_default_last_update_login,
14329                 current_calling_sequence) <> TRUE) THEN
14330             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14331               AP_IMPORT_UTILITIES_PKG.Print(
14332                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
14333                   'insert_rejections<-'||current_calling_sequence);
14334             END IF;
14335             CLOSE po_line_locations_cur;
14336             RAISE check_po_failure;
14337             --
14338           END IF; -- insert rejections
14339           l_current_invoice_status := 'N';
14340         END IF; -- code combination id is -1
14341       END IF;  -- overlay segments
14342 
14343       END LOOP;
14344       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14345         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14346           '(v_check_po_overlay 5) Close po_line_locations ');
14347       END IF;
14348       CLOSE po_line_locations_cur;
14349     END IF; -- po distribution id is not NULL
14350   ELSE -- invoice status <> 'N'
14351     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14352       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14353          '(v_check_po_overlay 1) No Overlay Required ');
14354     END IF;
14355 
14356   END IF; -- invoice status <> 'N'
14357 
14358   p_current_invoice_status := l_current_invoice_status;
14359   RETURN (TRUE);
14360 
14361 EXCEPTION
14362   WHEN OTHERS THEN
14363     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14364       AP_IMPORT_UTILITIES_PKG.Print(
14365         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14366     END IF;
14367 
14368     IF (SQLCODE < 0) THEN
14369       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14370         AP_IMPORT_UTILITIES_PKG.Print(
14371           AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
14372       END IF;
14373     END IF;
14374     RETURN(FALSE);
14375 
14376 END v_check_po_overlay;
14377 
14378 
14379 ------------------------------------------------------------------------------
14380 -- This function is used to validate RCV information.
14381 -- Retropricing:Step 1 and 3 don't execute for PPA's
14382 ------------------------------------------------------------------------------
14383 FUNCTION v_check_receipt_info (
14384    p_invoice_rec	IN    AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
14385    p_invoice_lines_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
14386    p_default_last_updated_by      IN            NUMBER,
14387    p_default_last_update_login    IN            NUMBER,
14388    p_temp_line_status                OUT NOCOPY VARCHAR2,
14389    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
14390 IS
14391    check_receipt_failure        EXCEPTION;
14392    l_temp_rcv_txn_id            NUMBER;
14393    l_temp_ship_line_id          NUMBER;     --Bug 7344899 variable added
14394    l_temp_value                    VARCHAR2(1);
14395    l_qty_billed_sum                NUMBER;
14396    l_rcv_uom                    VARCHAR2(30);
14397    l_qty_billed                    NUMBER;
14398    debug_info                    VARCHAR2(2000);
14399    current_calling_sequence        VARCHAR2(2000);
14400    l_cascade_receipts_flag      VARCHAR2(1);
14401    l_price_correct_inv_id	AP_INVOICES.INVOICE_ID%TYPE;
14402 
14403    --Contract Payments
14404    l_shipment_type		PO_LINE_LOCATIONS_ALL.SHIPMENT_TYPE%TYPE;
14405 
14406 BEGIN
14407 
14408   -- Update   the calling sequence
14409   current_calling_sequence :=
14410     'AP_IMPORT_VALIDATION_PKG.v_check_receipt_info <-' ||p_calling_sequence;
14411 
14412   --Contract Payments: Cannot match a Prepayment invoice to receipt.
14413   IF (p_invoice_rec.invoice_type_lookup_code = 'PREPAYMENT' AND
14414       (p_invoice_lines_rec.rcv_transaction_id IS NOT NULL OR
14415        p_invoice_lines_rec.match_option = 'R' OR
14416        p_invoice_lines_rec.receipt_number IS NOT NULL
14417       )
14418      ) THEN
14419 
14420       debug_info := '(Check Receipt Info 1) Check if invoice type is'||
14421       		   ' Prepayment and receipt info is provided';
14422       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14423          AP_IMPORT_UTILITIES_PKG.Print(
14424                  AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14425       END IF;
14426 
14427       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14428                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14429                    p_invoice_lines_rec.invoice_line_id,
14430                    'INVALID MATCHING INFO',
14431                    p_default_last_updated_by,
14432                    p_default_last_update_login,
14433                    current_calling_sequence)<> TRUE) THEN
14434           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14435              AP_IMPORT_UTILITIES_PKG.Print(
14436                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
14437                 'insert_rejections <-'||current_calling_sequence);
14438           END IF;
14439           Raise check_receipt_failure;
14440       END IF;
14441 
14442       p_temp_line_status := 'N';
14443 
14444   END IF;
14445 
14446   ---------------------------------------------------------------------------
14447   -- Step 1 : Validate receipt info IF source is EDI GATEWAY AND type = ITEM
14448   ---------------------------------------------------------------------------
14449 
14450 
14451   IF (AP_IMPORT_INVOICES_PKG.g_source = 'EDI GATEWAY') AND
14452      (p_invoice_lines_rec.line_type_lookup_code = 'ITEM') AND
14453      (p_invoice_lines_rec.match_option = 'R') THEN
14454 
14455 
14456     -- Case a : receipt_num AND id are NULL
14457     IF (p_invoice_lines_rec.receipt_number is NULL ) AND
14458        (p_invoice_lines_rec.rcv_transaction_id is NULL) AND
14459        (p_invoice_lines_rec.po_line_location_id is not NULL) THEN
14460 
14461        debug_info := '(Check Receipt Info 1) Case a';
14462       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14463           AP_IMPORT_UTILITIES_PKG.Print(
14464             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14465       END IF;
14466 
14467       BEGIN
14468        SELECT rcv_transaction_id
14469          INTO l_temp_rcv_txn_id
14470          FROM po_ap_receipt_match_v
14471         WHERE po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14472 
14473       EXCEPTION
14474         When no_data_found THEN
14475            -- reject fOR INSUFFICIENT RECEIPT INFORMATION
14476            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14477                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14478                 p_invoice_lines_rec.invoice_line_id,
14479                 'INSUFFICIENT RECEIPT INFO',
14480                 p_default_last_updated_by,
14481                 p_default_last_update_login,
14482                 current_calling_sequence)<> TRUE) THEN
14483              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14484                AP_IMPORT_UTILITIES_PKG.Print(
14485                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
14486                    'insert_rejections <-'||current_calling_sequence);
14487              END IF;
14488               Raise check_receipt_failure;
14489            END IF;
14490            p_temp_line_status := 'N';
14491         When too_many_rows THEN
14492              l_cascade_receipts_flag := 'Y';
14493           l_temp_rcv_txn_id := NULL;
14494       END;
14495 
14496       -- Case c : receipt num is not NULL, id is NULL
14497     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
14498         (p_invoice_lines_rec.rcv_transaction_id is NULL) THEN
14499       debug_info := '(Check Receipt Info 1) Case c';
14500       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14501         AP_IMPORT_UTILITIES_PKG.Print(
14502           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14503       END IF;
14504 
14505       BEGIN
14506        SELECT rcv_transaction_id
14507          INTO l_temp_rcv_txn_id
14508          FROM po_ap_receipt_match_v
14509         WHERE receipt_number = p_invoice_lines_rec.receipt_number
14510           AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14511 
14512        Exception
14513          When no_data_found THEN
14514        --reject fOR INVALID RECEIPT INFORMATION
14515        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14516             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14517             p_invoice_lines_rec.invoice_line_id,
14518             'INVALID RECEIPT INFO',
14519             p_default_last_updated_by,
14520             p_default_last_update_login,
14521             current_calling_sequence)<> TRUE) THEN
14522              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14523                AP_IMPORT_UTILITIES_PKG.Print(
14524                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
14525                    'insert_rejections <-'||current_calling_sequence);
14526              END IF;
14527          Raise check_receipt_failure;
14528        END IF;
14529        p_temp_line_status := 'N';
14530          WHEN too_many_rows THEN
14531            l_cascade_receipts_flag := 'Y';
14532        l_temp_rcv_txn_id := NULL;
14533       END;
14534 
14535     -- Case d : receipt_num is NULL AND id is not NULL
14536     ELSIF (p_invoice_lines_rec.receipt_number is NULL) AND
14537     (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
14538       debug_info := '(Check Receipt Info 1) Case d';
14539       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14540          AP_IMPORT_UTILITIES_PKG.Print(
14541            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14542       END IF;
14543 
14544       BEGIN
14545        SELECT rcv_transaction_id
14546        INTO l_temp_rcv_txn_id
14547        FROM po_ap_receipt_match_v
14548        WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
14549        AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14550 
14551        EXCEPTION
14552          When Others THEN
14553      -- reject fOR INVALID RECEIPT INFORMATION
14554          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14555             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14556             p_invoice_lines_rec.invoice_line_id,
14557             'INVALID RECEIPT INFO',
14558             p_default_last_updated_by,
14559             p_default_last_update_login,
14560             current_calling_sequence)<> TRUE) THEN
14561              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14562                AP_IMPORT_UTILITIES_PKG.Print(
14563                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
14564             'insert_rejections <-'||current_calling_sequence);
14565              END IF;
14566          Raise check_receipt_failure;
14567        END IF;
14568        p_temp_line_status := 'N';
14569       END;
14570 
14571     -- Case d : receipt num is not NULL AND id is not NULL
14572     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
14573           (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
14574       debug_info := '(Check Receipt Info 1) Case e';
14575       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14576         AP_IMPORT_UTILITIES_PKG.Print(
14577           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14578       END IF;
14579       BEGIN
14580        SELECT rcv_transaction_id
14581          INTO l_temp_rcv_txn_id
14582          FROM po_ap_receipt_match_v
14583         WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
14584           AND receipt_number = p_invoice_lines_rec.receipt_number
14585           AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14586 
14587 
14588       Exception
14589          When Others THEN
14590      -- reject fOR INCONSISTENT RECEIPT INFORMATION
14591          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14592             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14593             p_invoice_lines_rec.invoice_line_id,
14594             'INCONSISTENT RECEIPT INFO',
14595             p_default_last_updated_by,
14596             p_default_last_update_login,
14597             current_calling_sequence)<> TRUE) THEN
14598            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14599                AP_IMPORT_UTILITIES_PKG.Print(
14600                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
14601                    'insert_rejections <-'||current_calling_sequence);
14602            END IF;
14603        Raise check_receipt_failure;
14604      END IF;
14605      p_temp_line_status := 'N';
14606        END;
14607     END IF; -- Case a receipt number AND id are NULL
14608 
14609 
14610     -------------------------------------------------------------------
14611     -- Step 1.A  Validate UOM AND Quantity IF cascade flag = 'Y'
14612     -- Context: Source = 'EDI GATEWAY', line type = 'ITEM' AND
14613     -- Match Option = 'R'
14614     -------------------------------------------------------------------
14615     IF (nvl(l_cascade_receipts_flag,'N') = 'Y' )THEN
14616       -- Validate UOM
14617       IF (p_invoice_lines_rec.unit_of_meas_lookup_code is not NULL) THEN
14618         debug_info := 'validate the UOM';
14619         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14620           AP_IMPORT_UTILITIES_PKG.Print(
14621             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14622         END IF;
14623 
14624         BEGIN
14625         SELECT distinct receipt_uom_lookup_code
14626           INTO l_rcv_uom
14627           FROM po_ap_receipt_match_v
14628          WHERE po_line_location_id = p_invoice_lines_rec.po_line_location_id
14629            AND receipt_number = NVL(p_invoice_lines_rec.receipt_number,
14630                                         receipt_number)
14631            AND rcv_transaction_id = nvl(p_invoice_lines_rec.rcv_transaction_id,
14632                                         rcv_transaction_id);
14633         EXCEPTION
14634         WHEN OTHERS THEN
14635           -- reject with   UOM DOES NOT MATCH RECEIPT
14636           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14637                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14638                 p_invoice_lines_rec.invoice_line_id,
14639                 'UOM DOES NOT MATCH RECPT',
14640                 p_default_last_updated_by,
14641                 p_default_last_update_login,
14642                 current_calling_sequence)<> TRUE) THEN
14643                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14644                   AP_IMPORT_UTILITIES_PKG.Print(
14645                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
14646                 'insert_rejections <-'||current_calling_sequence);
14647                 END IF;
14648             Raise check_receipt_failure;
14649           END IF;
14650          END;
14651 
14652        IF (l_rcv_uom <> p_invoice_lines_rec.unit_of_meas_lookup_code) THEN
14653           -- reject with   UOM DOES NOT MATCH RECEIPT
14654           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14655                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14656                 p_invoice_lines_rec.invoice_line_id,
14657                 'UOM DOES NOT MATCH RECPT',
14658                 p_default_last_updated_by,
14659                 p_default_last_update_login,
14660                 current_calling_sequence)<> TRUE) THEN
14661                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14662                   AP_IMPORT_UTILITIES_PKG.Print(
14663                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
14664                       'insert_rejections <-'||current_calling_sequence);
14665                 END IF;
14666             Raise check_receipt_failure;
14667           END IF;
14668         END IF;
14669 
14670       END IF; -- unit of measure is not NULL
14671 
14672       -- Validate quantity billed does not become less than zero
14673       debug_info := 'Check IF quantity billed will be less than zero';
14674       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14675         AP_IMPORT_UTILITIES_PKG.Print(
14676           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14677       END IF;
14678 
14679       BEGIN
14680       --bug 5118518:Removed the view reference
14681           SELECT nvl(sum(nvl(RT.quantity_billed,0)),0)
14682             INTO l_qty_billed_sum
14683             FROM rcv_transactions RT ,
14684                  rcv_shipment_headers SH ,
14685                  po_headers_all PH ,
14686                  po_line_locations_all PS ,
14687                  po_releases_all PR ,
14688                  per_all_people_f BU
14689           WHERE  RT.po_line_location_id = p_invoice_lines_rec.po_line_location_id
14690             AND  SH.receipt_num     = nvl(p_invoice_lines_rec.receipt_number,sh.receipt_num)
14691             AND RT.transaction_id  = nvl(p_invoice_lines_rec.rcv_transaction_id, RT.transaction_id)
14692             AND RT.SHIPMENT_HEADER_ID  = SH.SHIPMENT_HEADER_ID
14693             AND RT.PO_HEADER_ID        = PH.PO_HEADER_ID
14694             AND RT.PO_LINE_LOCATION_ID = PS.LINE_LOCATION_ID
14695             AND RT.PO_RELEASE_ID       = PR.PO_RELEASE_ID(+)
14696             AND PH.AGENT_ID            = BU.PERSON_ID(+)
14697             AND SH.receipt_source_code = 'VENDOR'
14698             AND RT.TRANSACTION_TYPE IN ('RECEIVE', 'MATCH')
14699             AND BU.EFFECTIVE_START_DATE(+) <= TRUNC(SYSDATE)
14700             AND BU.EFFECTIVE_END_DATE(+)   >= TRUNC(SYSDATE)
14701             AND ((PS.PO_RELEASE_ID IS NOT NULL AND PR.PCARD_ID IS NULL) OR (PS.PO_RELEASE_ID IS NULL AND PH.PCARD_ID IS NULL ));
14702 
14703           IF ((p_invoice_lines_rec.quantity_invoiced + l_qty_billed_sum) < 0) THEN
14704           -- reject with   INVALID QUANTITY
14705             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14706                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14707                  p_invoice_lines_rec.invoice_line_id,
14708                  'INVALID QUANTITY',
14709                  p_default_last_updated_by,
14710                  p_default_last_update_login,
14711                  current_calling_sequence,
14712                  'Y',
14713                  'QUANTITY INVOICED',
14714                  p_invoice_lines_rec.quantity_invoiced + l_qty_billed_sum )
14715                  <> TRUE) THEN
14716               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14717                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14718                   'insert_rejections <-'||current_calling_sequence);
14719               END IF;
14720               Raise check_receipt_failure;
14721             END IF;
14722           END IF;
14723       END;
14724     END IF; -- cascade receipts flag = 'Y' --Step 1.A
14725 
14726   -------------------------------------------------------------------------
14727   -- Step 2 : Validate receipt info IF source is not
14728   -- EDI GATEWAY AND type = ITEM
14729   -- Retropricing: Match_option is populated as null for PPA Invoice lines,
14730   -- however the in v_check_line_po_info2, the value of match_option is determined and
14731   -- is assigned to p_invoice_lines_rec.match_option for further validation.
14732   -------------------------------------------------------------------------
14733   ELSIF (AP_IMPORT_INVOICES_PKG.g_source <> 'EDI GATEWAY') AND
14734         (p_invoice_lines_rec.line_type_lookup_code IN ('ITEM', 'RETROITEM')) AND
14735         (p_invoice_lines_rec.match_option = 'R') THEN
14736 
14737     -- Case a : receipt_num AND id are NULL
14738     IF  (p_invoice_lines_rec.receipt_number is NULL ) AND
14739         (p_invoice_lines_rec.rcv_transaction_id is NULL) AND
14740         (p_invoice_lines_rec.po_line_location_id is not NULL) THEN
14741       debug_info := '(Check Receipt Info 2) Case a';
14742       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14743         AP_IMPORT_UTILITIES_PKG.Print(
14744           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14745       END IF;
14746       -- reject fOR INSUFFICIENT RECEIPT INFORMATION
14747       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14748             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14749             p_invoice_lines_rec.invoice_line_id,
14750             'INSUFFICIENT RECEIPT INFO',
14751             p_default_last_updated_by,
14752             p_default_last_update_login,
14753             current_calling_sequence)<> TRUE) THEN
14754          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14755            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
14756              'insert_rejections <-'||current_calling_sequence);
14757          END IF;
14758          Raise check_receipt_failure;
14759       END IF;
14760       p_temp_line_status := 'N';
14761 
14762       -- Case b : receipt num is not NULL, id is NULL
14763     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
14764            (p_invoice_lines_rec.rcv_transaction_id is NULL) THEN
14765        debug_info := '(Check Receipt Info 2) Case b';
14766        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14767          AP_IMPORT_UTILITIES_PKG.Print(
14768            AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14769        END IF;
14770        BEGIN
14771         SELECT rcv_transaction_id
14772           INTO l_temp_rcv_txn_id
14773           FROM po_ap_receipt_match_v
14774          WHERE receipt_number = p_invoice_lines_rec.receipt_number
14775            AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14776 
14777         Exception
14778           When no_data_found THEN
14779           --reject fOR INVALID RECEIPT INFORMATION
14780           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14781                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14782                 p_invoice_lines_rec.invoice_line_id,
14783                 'INVALID RECEIPT INFO',
14784                 p_default_last_updated_by,
14785                 p_default_last_update_login,
14786                 current_calling_sequence)<> TRUE) THEN
14787                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14788                     AP_IMPORT_UTILITIES_PKG.Print(
14789                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
14790                         'insert_rejections <-'||current_calling_sequence);
14791                 END IF;
14792             Raise check_receipt_failure;
14793           END IF;
14794           p_temp_line_status := 'N';
14795         When too_many_rows THEN
14796             -- reject fOR INSUFFICIENT RECEIPT INFORMATION
14797             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14798                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14799                     p_invoice_lines_rec.invoice_line_id,
14800                     'INSUFFICIENT RECEIPT INFO',
14801                     p_default_last_updated_by,
14802                     p_default_last_update_login,
14803                     current_calling_sequence)<> TRUE) THEN
14804               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14805                 AP_IMPORT_UTILITIES_PKG.Print(
14806                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
14807                     'insert_rejections <-'||current_calling_sequence);
14808               END IF;
14809               Raise check_receipt_failure;
14810             END IF;
14811             p_temp_line_status := 'N';
14812         END;
14813 
14814      -- Case c : receipt_num is NULL AND id is not NULL
14815     ELSIF (p_invoice_lines_rec.receipt_number is NULL) AND
14816        (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
14817        debug_info := '(Check Receipt Info 2) Case c';
14818        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14819          AP_IMPORT_UTILITIES_PKG.Print(
14820            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14821        END IF;
14822 
14823        BEGIN
14824         SELECT rcv_transaction_id
14825           INTO l_temp_rcv_txn_id
14826           FROM po_ap_receipt_match_v
14827          WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
14828            AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14829 
14830        Exception
14831        WHEN Others THEN
14832          -- reject fOR INVALID RECEIPT INFORMATION
14833          IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14834                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14835                 p_invoice_lines_rec.invoice_line_id,
14836                 'INVALID RECEIPT INFO',
14837                 p_default_last_updated_by,
14838                 p_default_last_update_login,
14839                 current_calling_sequence)<> TRUE) THEN
14840                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14841                    AP_IMPORT_UTILITIES_PKG.Print(
14842                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
14843                   'insert_rejections <-'||current_calling_sequence);
14844                END IF;
14845            Raise check_receipt_failure;
14846          END IF;
14847          p_temp_line_status := 'N';
14848        END;
14849 
14850      -- Case d : receipt num is not NULL AND id is not NULL
14851     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
14852       (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
14853         debug_info := '(Check Receipt Info 2) Case d';
14854         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14855           AP_IMPORT_UTILITIES_PKG.Print(
14856             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14857         END IF;
14858 
14859         BEGIN
14860             SELECT rcv_transaction_id
14861               INTO l_temp_rcv_txn_id
14862               FROM po_ap_receipt_match_v
14863              WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
14864                AND receipt_number = p_invoice_lines_rec.receipt_number
14865                AND po_line_location_id = p_invoice_lines_rec.po_line_location_id;
14866 
14867         EXCEPTION
14868         When Others THEN
14869             -- reject fOR INCONSISTENT RECEIPT INFORMATION
14870             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14871                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14872                     p_invoice_lines_rec.invoice_line_id,
14873                     'INCONSISTENT RECEIPT INFO',
14874                     p_default_last_updated_by,
14875                     p_default_last_update_login,
14876                     current_calling_sequence)<> TRUE) THEN
14877                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14878                    AP_IMPORT_UTILITIES_PKG.Print(
14879                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
14880                    'insert_rejections <-'||current_calling_sequence);
14881                 END IF;
14882                 Raise check_receipt_failure;
14883             END IF;
14884         p_temp_line_status := 'N';
14885         END;
14886      END IF; -- Receipt number AND id are NULL
14887 
14888   -------------------------------------------------------------------------
14889   -- Step 3 : Validate receipt info IF type is not ITEM or RETROITEM AND
14890   -- some receipt info given
14891   -------------------------------------------------------------------------
14892   ELSIF (p_invoice_lines_rec.line_type_lookup_code IN
14893         ('TAX', 'MISCELLANEOUS','FREIGHT') AND
14894         (p_invoice_lines_rec.receipt_number IS NOT NULL OR
14895          p_invoice_lines_rec.rcv_transaction_id IS NOT NULL)) THEN
14896 
14897     -- Case a : receipt_num AND id are NULL
14898     -- ignore matching to receipt
14899 
14900     -- Case b : receipt num is not NULL, id is NULL
14901     IF (p_invoice_lines_rec.receipt_number is not NULL) AND
14902        (p_invoice_lines_rec.rcv_transaction_id is NULL) THEN
14903       debug_info := '(Check Receipt Info 3) Case b';
14904       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14905          AP_IMPORT_UTILITIES_PKG.Print(
14906          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14907       END IF;
14908       BEGIN
14909        SELECT rcv_transaction_id
14910          INTO l_temp_rcv_txn_id
14911          FROM po_ap_receipt_match_v
14912          WHERE receipt_number = p_invoice_lines_rec.receipt_number;
14913        Exception
14914        When no_data_found THEN
14915            --reject fOR INVALID RECEIPT INFORMATION
14916            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14917                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14918                 p_invoice_lines_rec.invoice_line_id,
14919                 'INVALID RECEIPT INFO',
14920                 p_default_last_updated_by,
14921                 p_default_last_update_login,
14922                 current_calling_sequence)<> TRUE) THEN
14923                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14924                    AP_IMPORT_UTILITIES_PKG.Print(
14925                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
14926                        'insert_rejections <-'||current_calling_sequence);
14927                  END IF;
14928              Raise check_receipt_failure;
14929            END IF;
14930            p_temp_line_status := 'N';
14931        When too_many_rows THEN
14932        -- reject fOR INSUFFICIENT RECEIPT INFORMATION
14933            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14934                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14935                 p_invoice_lines_rec.invoice_line_id,
14936                 'INSUFFICIENT RECEIPT INFO',
14937                 p_default_last_updated_by,
14938                 p_default_last_update_login,
14939                 current_calling_sequence)<> TRUE) THEN
14940                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14941                    AP_IMPORT_UTILITIES_PKG.Print(
14942                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
14943                      'insert_rejections <-'||current_calling_sequence);
14944                  END IF;
14945              Raise check_receipt_failure;
14946            END IF;
14947            p_temp_line_status := 'N';
14948        END;
14949 
14950     -- Case c : receipt_num is NULL AND id is not NULL
14951     ELSIF (p_invoice_lines_rec.receipt_number is NULL) AND
14952           (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
14953       debug_info := '(Check Receipt Info 3) Case c';
14954       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14955         AP_IMPORT_UTILITIES_PKG.Print(
14956           AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
14957       END IF;
14958       BEGIN
14959        SELECT rcv_transaction_id
14960          INTO l_temp_rcv_txn_id
14961          FROM po_ap_receipt_match_v
14962         WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id;
14963        Exception
14964          When Others THEN
14965            -- reject fOR INVALID RECEIPT INFORMATION
14966            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
14967             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
14968             p_invoice_lines_rec.invoice_line_id,
14969             'INVALID RECEIPT INFO',
14970             p_default_last_updated_by,
14971             p_default_last_update_login,
14972             current_calling_sequence)<> TRUE) THEN
14973                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14974                    AP_IMPORT_UTILITIES_PKG.Print(
14975                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
14976                        'insert_rejections <-'||current_calling_sequence);
14977                  END IF;
14978              Raise check_receipt_failure;
14979            END IF;
14980            p_temp_line_status := 'N';
14981        END;
14982 
14983     -- Case d : receipt num is not NULL AND id is not NULL
14984     ELSIF (p_invoice_lines_rec.receipt_number is not NULL) AND
14985       (p_invoice_lines_rec.rcv_transaction_id is not NULL) THEN
14986       debug_info := '(Check Receipt Info 3) Case d';
14987       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
14988          AP_IMPORT_UTILITIES_PKG.Print(
14989            AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
14990       END IF;
14991       BEGIN
14992        SELECT rcv_transaction_id
14993          INTO l_temp_rcv_txn_id
14994          FROM po_ap_receipt_match_v
14995         WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
14996           AND receipt_number = p_invoice_lines_rec.receipt_number;
14997        Exception
14998          When Others THEN
14999              -- reject for inconsistent receipt information
15000              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15001                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15002                     p_invoice_lines_rec.invoice_line_id,
15003                     'INCONSISTENT RECEIPT INFO',
15004                     p_default_last_updated_by,
15005                     p_default_last_update_login,
15006                     current_calling_sequence)<> TRUE) THEN
15007                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15008                    AP_IMPORT_UTILITIES_PKG.Print(
15009                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
15010                        'insert_rejections <-'||current_calling_sequence);
15011                  END IF;
15012                  Raise check_receipt_failure;
15013              END IF;
15014              p_temp_line_status := 'N';
15015                END;
15016             END IF; -- receipt number AND id are NULL.
15017   END IF; -- Source, line type AND match option (Step 1)
15018 
15019   -- copy l_temp_rcv_txn_id back to rcv_transaction id IF not NULL
15020   p_invoice_lines_rec.rcv_transaction_id :=
15021         nvl(l_temp_rcv_txn_id, p_invoice_lines_rec.rcv_transaction_id);
15022 
15023 	-- Getting the value of rcv_shipment_line_id -- Bug 7344899
15024 
15025    IF (p_invoice_lines_rec.rcv_transaction_id is not NULL)  THEN
15026         debug_info := '(Get the value of rcv_shipment_line_id) ';
15027       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15028          AP_IMPORT_UTILITIES_PKG.Print(
15029          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15030       END IF;
15031       BEGIN
15032        SELECT rcv_shipment_line_id
15033        INTO   l_temp_ship_line_id
15034        FROM po_ap_receipt_match_v
15035 	   WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id;
15036        Exception
15037        When no_data_found THEN
15038            --reject fOR INVALID RECEIPT INFORMATION
15039            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15040                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15041                 p_invoice_lines_rec.invoice_line_id,
15042                 'INVALID RECEIPT INFO',
15043                 p_default_last_updated_by,
15044                 p_default_last_update_login,
15045                 current_calling_sequence)<> TRUE) THEN
15046                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15047                    AP_IMPORT_UTILITIES_PKG.Print(
15048                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
15049                        'insert_rejections <-'||current_calling_sequence);
15050                  END IF;
15051              Raise check_receipt_failure;
15052            END IF;
15053            p_temp_line_status := 'N';
15054        When too_many_rows THEN
15055        -- reject fOR INSUFFICIENT RECEIPT INFORMATION
15056            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15057                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15058                 p_invoice_lines_rec.invoice_line_id,
15059                 'INSUFFICIENT RECEIPT INFO',
15060                 p_default_last_updated_by,
15061                 p_default_last_update_login,
15062                 current_calling_sequence)<> TRUE) THEN
15063                  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15064                    AP_IMPORT_UTILITIES_PKG.Print(
15065                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
15066                      'insert_rejections <-'||current_calling_sequence);
15067                  END IF;
15068              Raise check_receipt_failure;
15069            END IF;
15070            p_temp_line_status := 'N';
15071 
15072        END;
15073        END IF;
15074 	   --copy l_temp_ship_line_id back to rcv_shipment_line_id  IF not NULL
15075 
15076 	   p_invoice_lines_rec.rcv_shipment_line_id := l_temp_ship_line_id ; --Bug 7344899
15077 
15078 
15079   ---------------------------------------------------------------------------
15080   -- Step 4:  Validate the final match flag <> 'Y'
15081   ---------------------------------------------------------------------------
15082   debug_info := '(check receipt info 4) : Final Match flag';
15083   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15084     AP_IMPORT_UTILITIES_PKG.Print(
15085       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15086   END IF;
15087 
15088   IF (p_invoice_lines_rec.match_option = 'R') AND
15089      (nvl(p_invoice_lines_rec.final_match_flag,'N') = 'Y' ) THEN
15090     -- reject fOR INVALID FINAL MATCH FLAG
15091     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15092         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15093         p_invoice_lines_rec.invoice_line_id,
15094         'INVALID FINAL MATCH FLAG',
15095         p_default_last_updated_by,
15096         p_default_last_update_login,
15097         current_calling_sequence)<> TRUE) THEN
15098       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15099         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15100           'insert_rejections <-'||current_calling_sequence);
15101       END IF;
15102       Raise check_receipt_failure;
15103     END IF;
15104     p_temp_line_status := 'N';
15105   END IF;
15106 
15107   ----------------------------------------------------------------------------
15108   -- Step 5 : Validate the UOM  IF rcv_txn_id is not NULL
15109   ----------------------------------------------------------------------------
15110   IF (p_invoice_lines_rec.rcv_transaction_id IS NOT NULL)  AND
15111      (p_invoice_lines_rec.match_option = 'R') AND
15112      (p_invoice_lines_rec.unit_of_meas_lookup_code IS NOT NULL) THEN
15113 
15114     debug_info := '(check receipt info 5) : Validate UOM';
15115     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15116       AP_IMPORT_UTILITIES_PKG.Print(
15117         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15118     END IF;
15119     BEGIN
15120       SELECT 'Y'
15121         INTO l_temp_value
15122         FROM po_ap_receipt_match_v
15123        WHERE rcv_transaction_id = p_invoice_lines_rec.rcv_transaction_id
15124          AND receipt_uom_lookup_code =
15125              p_invoice_lines_rec.unit_of_meas_lookup_code;
15126     EXCEPTION
15127       WHEN OTHERS THEN
15128         -- reject for uom does not match receipt
15129         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15130             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15131             p_invoice_lines_rec.invoice_line_id,
15132             'UOM DOES NOT MATCH RECPT',
15133             p_default_last_updated_by,
15134             p_default_last_update_login,
15135             current_calling_sequence)<> TRUE) THEN
15136           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15137             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15138               'insert_rejections <-'||current_calling_sequence);
15139           END IF;
15140       Raise check_receipt_failure;
15141         END IF;
15142         p_temp_line_status := 'N';
15143     END;
15144   END IF;
15145 
15146   ----------------------------------------------------------------------------
15147   -- Step 6 : Validate IF prorate is checked AND receipt info provided
15148   -- for non Item.
15149   -- Retropricing: PPA Invoice Line will not have TAX and there the code
15150   -- below will not get executed.
15151   ----------------------------------------------------------------------------
15152   debug_info := '(check receipt info 6) : Check prorate flag';
15153   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15154     AP_IMPORT_UTILITIES_PKG.Print(
15155       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15156   END IF;
15157 
15158   IF (p_invoice_lines_rec.line_type_lookup_code IN
15159      ('MISCELLANEOUS', 'FREIGHT','TAX') AND
15160       NVL(p_invoice_lines_rec.prorate_across_flag,'N') = 'Y' AND
15161       (p_invoice_lines_rec.receipt_number is not NULL OR
15162       p_invoice_lines_rec.rcv_transaction_id is not NULL) ) THEN
15163 
15164     -- reject for inconsistent allocation info
15165     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15166             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15167             p_invoice_lines_rec.invoice_line_id,
15168             'INCONSISTENT ALLOC INFO',
15169             p_default_last_updated_by,
15170             p_default_last_update_login,
15171             current_calling_sequence)<> TRUE) THEN
15172       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15173         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15174           'insert_rejections <-'||current_calling_sequence);
15175       END IF;
15176       Raise check_receipt_failure;
15177     END IF;
15178     p_temp_line_status := 'N';
15179   END IF;
15180 
15181   ---------------------------------------------------------------------------
15182   -- step 7 : Validate quantity billed does not become less than zero ,
15183   --          IF rcv_transaction-id is not NULL AND is valid.
15184   -- Retropricing: Quantity Billed is not affected by Retropricing. This
15185   -- validation should be bypassed for PPA's.
15186   ---------------------------------------------------------------------------
15187   IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA' THEN
15188       IF (p_invoice_lines_rec.rcv_transaction_id is not NULL) AND
15189          (p_temp_line_status <> 'N') AND
15190          (p_invoice_lines_rec.match_option = 'R') AND
15191          (p_invoice_lines_rec.quantity_invoiced is not NULL) THEN
15192         debug_info := '(Check receipt info 7) : check Quantity billed';
15193         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15194           AP_IMPORT_UTILITIES_PKG.Print(
15195             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15196         END IF;
15197 
15198         BEGIN
15199           SELECT nvl(quantity_billed,0)
15200             INTO l_qty_billed
15201             FROM rcv_transactions
15202            WHERE transaction_id = p_invoice_lines_rec.rcv_transaction_id;
15203 
15204           IF (l_qty_billed +  p_invoice_lines_rec.quantity_invoiced ) < 0 THEN
15205             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15206                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15207                p_invoice_lines_rec.invoice_line_id,
15208                'INVALID QUANTITY',
15209                p_default_last_updated_by,
15210                p_default_last_update_login,
15211                current_calling_sequence,
15212                'Y',
15213                'QUANTITY INVOICED',
15214                l_qty_billed + p_invoice_lines_rec.quantity_invoiced )<> TRUE) THEN
15215               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15216                 AP_IMPORT_UTILITIES_PKG.Print(
15217                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
15218                     'insert_rejections <-'||current_calling_sequence);
15219               END IF;
15220               Raise check_receipt_failure;
15221             END IF;
15222             p_temp_line_status := 'N';
15223           END IF;
15224         END;
15225       END IF; -- rcv_txn_id not NULL
15226   END IF; --source <> PPA
15227   -- p_temp_line_status has the return value
15228   RETURN (TRUE);
15229 
15230 EXCEPTION
15231   When OTHERS THEN
15232     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15233       AP_IMPORT_UTILITIES_PKG.Print(
15234         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15235     END IF;
15236 
15237     IF (SQLCODE < 0) THEN
15238       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15239         AP_IMPORT_UTILITIES_PKG.Print(
15240           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
15241       END IF;
15242     END IF;
15243     Return(FALSE);
15244 
15245 END v_check_receipt_info;
15246 
15247 
15248 
15249 -----------------------------------------------------------------------------
15250 -- This function is used to validate line level accounting date information.
15251 --
15252 FUNCTION v_check_line_accounting_date (
15253    p_invoice_rec        IN
15254     AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
15255    p_invoice_lines_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
15256    p_gl_date_from_get_info        IN            DATE,
15257    p_gl_date_from_receipt_flag    IN            VARCHAR2,
15258    p_set_of_books_id              IN            NUMBER,
15259    p_purch_encumbrance_flag       IN            VARCHAR2,
15260    p_default_last_updated_by      IN            NUMBER,
15261    p_default_last_update_login    IN            NUMBER,
15262    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
15263    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
15264 IS
15265    check_accounting_date_failure  EXCEPTION;
15266    l_period_name                  VARCHAR2(15);
15267    l_dummy                          VARCHAR2(100);
15268    l_key                            VARCHAR2(1000);
15269    l_numof_values                   NUMBER;
15270    l_valueOut                   fnd_plsql_cache.generic_cache_value_type;
15271    l_values                     fnd_plsql_cache.generic_cache_values_type;
15272    l_ret_code                      VARCHAR2(1);
15273    l_exception                     VARCHAR2(10);
15274    l_current_invoice_status         VARCHAR2(1) := 'Y';
15275    l_accounting_date             DATE := p_invoice_lines_rec.accounting_date;
15276    current_calling_sequence       VARCHAR2(2000);
15277    debug_info                    VARCHAR2(500);
15278 
15279 BEGIN
15280   -- Update the calling sequence
15281   --
15282   current_calling_sequence :=
15283      'AP_IMPORT_VALIDATION_PKG.v_check_line_accounting_date<-'
15284      ||P_calling_sequence;
15285 
15286   --------------------------------------------------------------------------
15287   -- IF the accounting date is not specified in the Lines Interface use
15288   -- gl_date_from_invoice, IF null, THEN use gl_date_from_get_info as the
15289   -- acct date. Logic for deriving p_gl_date_from_get_info : Use GL Date
15290   -- from  Report input params
15291   -- IF null ,THEN
15292   --   IF p_gl_date_from_receipt_flag = 'I','N' THEN Invoice Date is
15293   --   used as the Gl Date
15294   --     IF invoice date is null use the sysdate as the invoice date/ GL_Date
15295   --   ElsIF p_gl_date_from_receipt_flag IN 'S','Y'   ,THEN use sydate as
15296   -- the GL Date.
15297   ---------------------------------------------------------------------------
15298   IF (l_accounting_date IS NULL) AND (p_invoice_rec.gl_date IS NOT NULL) THEN
15299     debug_info := '(Check_line_accounting_date 1) Default '
15300                   ||'line_accounting_date from Invoice gl_date';
15301     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15302       AP_IMPORT_UTILITIES_PKG.Print(
15303         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15304     END IF;
15305 
15306     l_accounting_date := p_invoice_rec.gl_date;
15307 
15308   ELSIF (l_accounting_date IS NULL) AND (p_gl_date_from_get_info IS NOT NULL)
15309     THEN
15310     debug_info := '(v_check_line_accounting_date 1) GL Date is Null in '
15311                   ||'Interface, Use gl_date from Get Info';
15312     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15313       AP_IMPORT_UTILITIES_PKG.Print(
15314         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15315     END IF;
15316     l_accounting_date := p_gl_date_from_get_info;
15317   END IF;
15318 
15319   IF ((l_accounting_date IS NULL) AND
15320       (p_gl_date_from_receipt_flag IN ('I','N')) AND
15321       (p_invoice_rec.invoice_date is NOT NULL)) THEN
15322     debug_info := '(v_check_line_accounting_date 2) GL Date is Invoice Date';
15323     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15324       AP_IMPORT_UTILITIES_PKG.Print(
15325         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15326     END IF;
15327     l_accounting_date := p_invoice_rec.invoice_date;
15328   ELSIF((l_accounting_date IS NULL) AND
15329         (p_gl_date_from_receipt_flag IN ('I','N')) AND
15330         (p_invoice_rec.invoice_date is NULL)) THEN
15331     debug_info := '(v_check_line_accounting_date 2) GL Date is sysdate';
15332     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15333       AP_IMPORT_UTILITIES_PKG.Print(
15334         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15335     END IF;
15336     l_accounting_date := AP_IMPORT_INVOICES_PKG.g_inv_sysdate;
15337   END IF;
15338 
15339   ------------------------------------------------------------------------
15340   -- Reject IF account_date is not in open period
15341   ------------------------------------------------------------------------
15342   debug_info := '(v_check_line_accounting_date 3) Check IF gl date is not '
15343                 ||'in open period';
15344   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15345     AP_IMPORT_UTILITIES_PKG.Print(
15346       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15347   END IF;
15348 
15349   -- bug 2496185 by isartawi .. cache the code_combination_ids
15350   l_key := TO_CHAR(p_set_of_books_id)||' '||
15351            TO_CHAR(NVL(l_accounting_date,
15352                        AP_IMPORT_INVOICES_PKG.g_inv_sysdate),'dd-mm-yyyy');
15353 
15354   fnd_plsql_cache.generic_1tom_get_values(
15355               AP_IMPORT_INVOICES_PKG.lg_many_controller,
15356               AP_IMPORT_INVOICES_PKG.lg_generic_storage,
15357               l_key,
15358               l_numof_values,
15359               l_values,
15360               l_ret_code);
15361 
15362   IF l_ret_code = '1' THEN --  means l_key found in cache
15363     l_period_name := l_values(1).varchar2_1;
15364     l_exception   := l_values(1).varchar2_2;
15365     IF l_exception = 'TRUE' THEN
15366       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15367           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15368           p_invoice_lines_rec.invoice_line_id,
15369           'ACCT DATE NOT IN OPEN PD',
15370           p_default_last_updated_by,
15371           p_default_last_update_login,
15372           current_calling_sequence) <> TRUE) THEN
15373         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15374           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15375             'insert_rejections<-'||current_calling_sequence);
15376         END IF;
15377         RAISE check_accounting_date_failure;
15378       END IF;
15379 
15380         --Bug3302807 Setting the l_current_invoice_status to 'N' if rejected
15381          l_current_invoice_status := 'N';
15382 
15383    END IF; -- l_exception TRUE
15384   ELSE  -- IF l_key not found in cache(l_ret_code other than 1) .. cache it
15385     BEGIN
15386       SELECT period_name
15387         INTO l_period_name
15388         FROM gl_period_statuses
15389        WHERE application_id = 200
15390          AND set_of_books_id = p_set_of_books_id
15391          AND trunc(nvl(l_accounting_date,AP_IMPORT_INVOICES_PKG.g_inv_sysdate))
15392              between start_date and END_date
15393          AND closing_status in ('O', 'F')
15394          AND NVL(adjustment_period_flag, 'N') = 'N';
15395 
15396       l_exception           := 'FALSE';
15397       l_valueOut.varchar2_1 := l_period_name;
15398       l_valueOut.varchar2_2 := l_exception;
15399       l_values(1)           := l_valueOut;
15400       l_numof_values        := 1;
15401 
15402       fnd_plsql_cache.generic_1tom_put_values(
15403                   AP_IMPORT_INVOICES_PKG.lg_many_controller,
15404                   AP_IMPORT_INVOICES_PKG.lg_generic_storage,
15405                   l_key,
15406                   l_numof_values,
15407                   l_values);
15408     EXCEPTION
15409       WHEN NO_DATA_FOUND THEN
15410         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15411           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15412             'Accounting date is not in open period');
15413         END IF;
15414 
15415         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15416             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15417              p_invoice_lines_rec.invoice_line_id,
15418             'ACCT DATE NOT IN OPEN PD',
15419             p_default_last_updated_by,
15420             p_default_last_update_login,
15421             current_calling_sequence) <> TRUE) THEN
15422           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15423             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15424               'insert_rejections<-'||current_calling_sequence);
15425           END IF;
15426           RAISE check_accounting_date_failure;
15427         END IF;
15428         l_current_invoice_status := 'N';
15429         l_exception              := 'TRUE';
15430         l_valueOut.varchar2_1    := NULL;
15431         l_valueOut.varchar2_2    := l_exception;
15432         l_values(1)              := l_valueOut;
15433         l_numof_values           := 1;
15434 
15435         fnd_plsql_cache.generic_1tom_put_values(
15436                     AP_IMPORT_INVOICES_PKG.lg_many_controller,
15437                     AP_IMPORT_INVOICES_PKG.lg_generic_storage,
15438                     l_key,
15439                     l_numof_values,
15440                     l_values);
15441     END;
15442   END IF; -- IF ret_code is 1
15443   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15444     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15445         '------------------> l_period_name = '|| l_period_name
15446     ||'l_accounting_date = '||to_char(l_accounting_date));
15447   END IF;
15448 
15449   --------------------------------------------------------------------------
15450   -- Reject IF the year of gl date is beyond encumbrance year
15451   -- only IF purch_encumbrance_flag = 'Y'
15452   --------------------------------------------------------------------------
15453   IF (p_purch_encumbrance_flag = 'Y') THEN
15454     BEGIN
15455       debug_info := '(v_check_line_accounting_date 4) Reject IF the year of '
15456                     ||'gl date is beyond encumbrance year';
15457       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15458         AP_IMPORT_UTILITIES_PKG.Print(
15459           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15460       END IF;
15461 
15462       SELECT 'The period is NOT beyond latest encumbrance year'
15463         INTO l_DUMMY
15464         FROM GL_PERIOD_STATUSES gps1,
15465              GL_SETS_OF_BOOKS gsob
15466        WHERE gps1.period_year <= gsob.latest_encumbrance_year
15467          AND gsob.SET_OF_BOOKS_ID = p_set_of_books_id
15468          AND gps1.APPLICATION_ID = 200
15469          AND gps1.SET_OF_BOOKS_ID = gsob.SET_OF_BOOKS_ID
15470          AND trunc(nvl(l_accounting_date,AP_IMPORT_INVOICES_PKG.g_inv_sysdate))
15471              BETWEEN gps1.START_DATE AND gps1.END_DATE
15472          AND gps1.closing_status in ('O', 'F')
15473          AND NVL(gps1.adjustment_period_flag, 'N') = 'N';
15474 
15475     EXCEPTION
15476       WHEN NO_DATA_FOUND THEN
15477         --
15478         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15479           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15480             'Accounting date is beyond encumbrance year');
15481         END IF;
15482 
15483         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15484            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15485             p_invoice_lines_rec.invoice_line_id,
15486             'ACCT DATE BEYOND ENC YEAR',
15487             p_default_last_updated_by,
15488             p_default_last_update_login,
15489             current_calling_sequence) <> TRUE) THEN
15490           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15491             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15492             'insert_rejections<-'||current_calling_sequence);
15493           END IF;
15494           RAISE check_accounting_date_failure;
15495         END IF;
15496         --
15497         l_current_invoice_status := 'N';
15498     END;
15499   END IF; -- purch encumbrance flag is Y
15500 
15501   IF (l_current_invoice_status = 'Y') THEN
15502     IF (l_accounting_date is not NULL) THEN
15503       p_invoice_lines_rec.accounting_date := l_accounting_date;
15504     END IF;
15505     IF (l_period_name is not NULL) THEN
15506       p_invoice_lines_rec.period_name := l_period_name;
15507     END IF;
15508   END IF;
15509   -- Return value
15510   p_current_invoice_status := l_current_invoice_status;
15511 
15512   RETURN (TRUE);
15513 EXCEPTION
15514   WHEN OTHERS THEN
15515     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15516       AP_IMPORT_UTILITIES_PKG.Print(
15517         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15518     END IF;
15519 
15520     IF (SQLCODE < 0) THEN
15521       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15522         AP_IMPORT_UTILITIES_PKG.Print(
15523           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
15524       END IF;
15525     END IF;
15526     RETURN(FALSE);
15527 
15528 END v_check_line_accounting_date;
15529 
15530 ------------------------------------------------------------------------------
15531 -- This function is used to validate line level project information.
15532 -- Retropricing:
15533 -- For the validation of PPA Invoice Lines , we will not be calling the
15534 -- PA Flexbuilder. We only verify if the Project level infomation
15535 -- is correct. Also we will bypass the rejection -- 'INCONSISTENT DIST INFO
15536 -- when both po and pa information co-exist.
15537 ------------------------------------------------------------------------------
15538 
15539 FUNCTION v_check_line_project_info (
15540    p_invoice_rec         IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
15541    p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
15542    p_accounting_date           IN            DATE,
15543    p_pa_installed              IN            VARCHAR2,
15544    p_employee_id               IN            NUMBER,
15545    p_base_currency_code        IN            VARCHAR2,
15546    p_set_of_books_id           IN            NUMBER,
15547    p_chart_of_accounts_id      IN            NUMBER,
15548    p_default_last_updated_by   IN            NUMBER,
15549    p_default_last_update_login IN            NUMBER,
15550    p_pa_built_account             OUT NOCOPY NUMBER,
15551    p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
15552    p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
15553 IS
15554 
15555 check_project_failure          EXCEPTION;
15556 l_current_invoice_status      VARCHAR2(1) := 'Y';
15557 l_error_found                  VARCHAR2(1) := 'N';
15558 l_pa_default_dist_ccid          NUMBER;
15559 l_pa_concatenated_segments    VARCHAR2(2000):='';
15560 l_dist_code_combination_id    NUMBER ;
15561 l_award_id                      NUMBER;
15562 l_unbuilt_flex                VARCHAR2(240):='';
15563 l_reason_unbuilt_flex         VARCHAR2(2000):='';
15564 current_calling_sequence      VARCHAR2(2000);
15565 debug_info                     VARCHAR2(500);
15566 l_key                         VARCHAR2(1000);
15567 l_numof_values                NUMBER;
15568 l_valueOut                    fnd_plsql_cache.generic_cache_value_type;
15569 l_values                      fnd_plsql_cache.generic_cache_values_type;
15570 l_ret_code                    VARCHAR2(1);
15571 l_validate_res                VARCHAR2(10);
15572 
15573 BEGIN
15574   -- Update the calling sequence
15575   --
15576   current_calling_sequence :=
15577     'AP_IMPORT_VALIDATION_PKG.v_check_line_project_info<-'
15578     ||P_calling_sequence;
15579 
15580   l_award_id := p_invoice_lines_rec.award_id ;
15581 
15582   IF (p_invoice_lines_rec.project_id IS NOT NULL  AND
15583       AP_IMPORT_INVOICES_PKG.g_source <> 'PPA') THEN
15584 
15585     ---------------------------------------------------------------------
15586     -- Step 1 - Reject IF line has PA info and it is PO matched
15587     -- or contains a default account (conflict of account sources)
15588 
15589     ---------------------------------------------------------------------
15590     debug_info := '(v_check_line_project_info 1) Check IF line has PA Info'
15591                   ||' and other account info as well';
15592     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15593       AP_IMPORT_UTILITIES_PKG.Print(
15594         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15595     END IF;
15596 
15597     IF ( p_invoice_lines_rec.po_number IS NOT NULL    OR
15598          p_invoice_lines_rec.po_header_id IS NOT NULL ) THEN
15599       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15600         AP_IMPORT_UTILITIES_PKG.Print(
15601           AP_IMPORT_INVOICES_PKG.g_debug_switch,
15602             '(v_check_line_project_info 2) Line with additional account'
15603             ||' info:Reject');
15604       END IF;
15605 
15606 
15607       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15608           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15609            p_invoice_lines_rec.invoice_line_id,
15610              'INCONSISTENT DIST INFO',
15611            p_default_last_updated_by,
15612            p_default_last_update_login,
15613            current_calling_sequence) <> TRUE) THEN
15614         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15615           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15616             'insert_rejections<-'||current_calling_sequence);
15617         END IF;
15618         RAISE check_project_failure;
15619       END IF;
15620 
15621       --
15622       l_current_invoice_status := 'N';
15623 
15624     END IF; -- po number or po header id are not null
15625 
15626     --------------------------------------------------------------
15627     -- Step 2
15628     -- Check for minimum info required for PA Flexbuild
15629     -- Else reject
15630     --------------------------------------------------------------
15631     IF (p_invoice_lines_rec.expenditure_item_date is NULL) then
15632       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
15633         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15634         '(v_check_line_project_info 2) Get expenditure item date');
15635       END IF;
15636 
15637         p_invoice_lines_rec.expenditure_item_date :=
15638           AP_INVOICES_PKG.get_expenditure_item_date(
15639             p_invoice_rec.invoice_id,
15640             p_invoice_rec.invoice_date,
15641             p_accounting_date,
15642             NULL,
15643             NULL,
15644             l_error_found);
15645 
15646       IF (l_error_found = 'Y') then
15647         RAISE check_project_failure;
15648       END IF;
15649     END IF; -- Expenditure item date is null
15650 
15651     IF ((p_invoice_lines_rec.project_id IS NULL) OR
15652         (p_invoice_lines_rec.task_id IS NULL) OR
15653         (p_invoice_lines_rec.expenditure_type IS NULL) OR
15654         (p_invoice_lines_rec.expenditure_item_date IS NULL) OR
15655         (p_invoice_lines_rec.expenditure_organization_id IS NULL)) THEN
15656       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15657         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15658         '(v_check_line_project_info 2) Insufficient PA Info:Reject');
15659       END IF;
15660 
15661       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15662             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15663              p_invoice_lines_rec.invoice_line_id,
15664             'INSUFFICIENT PA INFO',
15665              p_default_last_updated_by,
15666              p_default_last_update_login,
15667              current_calling_sequence) <> TRUE) THEN
15668         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15669               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15670             'insert_rejections<-'||current_calling_sequence);
15671         END IF;
15672         RAISE check_project_failure;
15673       END IF;
15674       --
15675       l_current_invoice_status := 'N';
15676     END IF;
15677 
15678     -- We need to call the GMS API only when the current invoice status
15679     -- is 'Y' and l_award_id is not null
15680     -- Else ignore the call.
15681     IF ( l_current_invoice_status = 'Y' AND p_invoice_lines_rec.project_id is not null ) THEN
15682       debug_info := 'AWARD_ID_REQUEST :(v_check_line_award_info 1) Check  '
15683                     ||'GMS Info ';
15684       IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch) THEN
15685         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15686           AP_IMPORT_UTILITIES_PKG.Print(
15687             AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
15688         END IF;
15689       END IF;
15690 
15691       IF    ( GMS_AP_API.v_check_line_award_info (
15692                   p_invoice_lines_rec.invoice_line_id,
15693                   p_invoice_lines_rec.amount,
15694                   p_invoice_lines_rec.base_amount,
15695                   p_invoice_lines_rec.dist_code_concatenated,
15696                   p_invoice_lines_rec.dist_code_combination_id,
15697                   p_invoice_rec.po_number,
15698                   p_invoice_lines_rec.po_number,
15699                   p_invoice_lines_rec.po_header_id,
15700                   p_invoice_lines_rec.distribution_set_id,
15701                   p_invoice_lines_rec.distribution_set_name,
15702                   p_set_of_books_id,
15703                   p_base_currency_code,
15704                   p_invoice_rec.invoice_currency_code,
15705                   p_invoice_rec.exchange_rate,
15706                   p_invoice_rec.exchange_rate_type,
15707                   p_invoice_rec.exchange_date,
15708                   p_invoice_lines_rec.project_id,
15709                   p_invoice_lines_rec.task_id,
15710                   p_invoice_lines_rec.expenditure_type,
15711                   p_invoice_lines_rec.expenditure_item_date,
15712                   p_invoice_lines_rec.expenditure_organization_id,
15713                   NULL, -- project_accounting_context
15714                   p_invoice_lines_rec.pa_addition_flag,
15715                   p_invoice_lines_rec.pa_quantity,
15716                   p_employee_id,
15717                   p_invoice_rec.vendor_id,
15718                   p_chart_of_accounts_id,
15719                   p_pa_installed,
15720                   p_invoice_lines_rec.prorate_across_flag,
15721                   p_invoice_lines_rec.attribute_category,
15722                   p_invoice_lines_rec.attribute1,
15723                   p_invoice_lines_rec.attribute2,
15724                   p_invoice_lines_rec.attribute3,
15725                   p_invoice_lines_rec.attribute4,
15726                   p_invoice_lines_rec.attribute5,
15727                   p_invoice_lines_rec.attribute6,
15728                   p_invoice_lines_rec.attribute7,
15729                   p_invoice_lines_rec.attribute8,
15730                   p_invoice_lines_rec.attribute9,
15731                   p_invoice_lines_rec.attribute10,
15732                   p_invoice_lines_rec.attribute11,
15733                   p_invoice_lines_rec.attribute12,
15734                   p_invoice_lines_rec.attribute13,
15735                   p_invoice_lines_rec.attribute14,
15736                   p_invoice_lines_rec.attribute15,
15737                   p_invoice_rec.attribute_category,
15738                   p_invoice_rec.attribute1,
15739                   p_invoice_rec.attribute2,
15740                   p_invoice_rec.attribute3,
15741                   p_invoice_rec.attribute4,
15742                   p_invoice_rec.attribute5,
15743                   p_invoice_rec.attribute6,
15744                   p_invoice_rec.attribute7,
15745                   p_invoice_rec.attribute8,
15746                   p_invoice_rec.attribute9,
15747                   p_invoice_rec.attribute10,
15748                   p_invoice_rec.attribute11,
15749                   p_invoice_rec.attribute12,
15750                   p_invoice_rec.attribute13,
15751                   p_invoice_rec.attribute14,
15752                   p_invoice_rec.attribute15,
15753                   p_invoice_lines_rec.partial_segments,
15754                   p_default_last_updated_by,
15755                   p_default_last_update_login,
15756                   p_calling_sequence,
15757                   l_award_id,
15758                   'AWARD_SET_ID_REQUEST' ) <> TRUE ) THEN
15759         IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch)
15760           THEN
15761           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15762             '(v_check_line_project_info 3) Invalid GMS Info:Reject');
15763         END IF;
15764 
15765         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15766                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15767                 p_invoice_lines_rec.invoice_line_id,
15768                 'INSUFFICIENT GMS INFO',
15769                 p_default_last_updated_by,
15770                 p_default_last_update_login,
15771                 current_calling_sequence) <> TRUE) THEN
15772           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15773             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15774               'insert_rejections<-'||current_calling_sequence);
15775           END IF;
15776           RAISE check_project_failure;
15777         END IF;
15778         --
15779         l_current_invoice_status := 'N';
15780       END IF;
15781     END IF; -- l_current_invoice_status = 'Y' and l_award_id is not null
15782 
15783     ------------------------------------------------------------------------
15784     -- Step 3
15785     -- IF invoice status is Y THEN Flexbuild
15786     ------------------------------------------------------------------------
15787     IF (l_current_invoice_status = 'Y') THEN
15788       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15789         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15790           '(v_check_line_project_info 4) Call pa_flexbuild');
15791       END IF;
15792       IF (AP_IMPORT_INVOICES_PKG.g_source <> 'PPA')  THEN
15793           IF (AP_IMPORT_UTILITIES_PKG.pa_flexbuild(
15794                  p_invoice_rec,                      -- IN
15795                  p_invoice_lines_rec,                -- IN OUT NOCOPY
15796                  p_accounting_date,                      -- IN
15797                  p_pa_installed,                     -- IN
15798                  p_employee_id,                     -- IN
15799                  p_base_currency_code,                -- IN
15800                  p_chart_of_accounts_id,             -- IN
15801                  p_default_last_updated_by,          -- IN
15802                  p_default_last_update_login,        -- IN
15803                  p_pa_default_dist_ccid     => l_pa_default_dist_ccid,    -- OUT NOCOPY
15804                  p_pa_concatenated_segments => l_pa_concatenated_segments,-- OUT NOCOPY
15805                  p_current_invoice_status   => l_current_invoice_status,  -- OUT NOCOPY
15806                  p_calling_sequence         => current_calling_sequence) <> TRUE) THEN
15807 
15808 
15809             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15810               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15811                 'insert_rejections<-'||current_calling_sequence);
15812             END IF;
15813             RAISE check_project_failure;
15814           END IF; -- pa flexbuild
15815       END IF; -- source <> PPA
15816 
15817       -- Added following IF condition so that GMS API will be
15818       -- called only when award_id is not null
15819       IF (l_current_invoice_status = 'Y' AND l_award_id is not null) THEN
15820         debug_info := 'AWARD_ID_REMOVE :(v_check_line_award_info 1) Check  GMS Info ';
15821         IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch)
15822           THEN
15823           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15824             AP_IMPORT_UTILITIES_PKG.Print(
15825               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
15826           END IF;
15827         END IF;
15828 
15829         IF GMS_AP_API.v_check_line_award_info (
15830                     p_invoice_lines_rec.invoice_line_id    ,
15831                     p_invoice_lines_rec.amount,
15832                     p_invoice_lines_rec.base_amount,
15833                     p_invoice_lines_rec.dist_code_concatenated,
15834                     p_invoice_lines_rec.dist_code_combination_id,
15835                     p_invoice_rec.po_number,
15836                     p_invoice_lines_rec.po_number,
15837                     p_invoice_lines_rec.po_header_id,
15838                     p_invoice_lines_rec.distribution_set_id,
15839                     p_invoice_lines_rec.distribution_set_name,
15840                     p_set_of_books_id,
15841                     p_base_currency_code,
15842                     p_invoice_rec.invoice_currency_code,
15843                     p_invoice_rec.exchange_rate,
15844                     p_invoice_rec.exchange_rate_type,
15845                     p_invoice_rec.exchange_date,
15846                     p_invoice_lines_rec.project_id,
15847                     p_invoice_lines_rec.task_id,
15848                     p_invoice_lines_rec.expenditure_type,
15849                     p_invoice_lines_rec.expenditure_item_date,
15850                     p_invoice_lines_rec.expenditure_organization_id,
15851                     NULL, --p_project_accounting_context
15852                     p_invoice_lines_rec.pa_addition_flag,
15853                     p_invoice_lines_rec.pa_quantity,
15854                     p_employee_id,
15855                     p_invoice_rec.vendor_id,
15856                     p_chart_of_accounts_id,
15857                     p_pa_installed,
15858                     p_invoice_lines_rec.prorate_across_flag,
15859                     p_invoice_lines_rec.attribute_category,
15860                     p_invoice_lines_rec.attribute1,
15861                     p_invoice_lines_rec.attribute2,
15862                     p_invoice_lines_rec.attribute3,
15863                     p_invoice_lines_rec.attribute4,
15864                     p_invoice_lines_rec.attribute5,
15865                     p_invoice_lines_rec.attribute6,
15866                     p_invoice_lines_rec.attribute7,
15867                     p_invoice_lines_rec.attribute8,
15868                     p_invoice_lines_rec.attribute9,
15869                     p_invoice_lines_rec.attribute10,
15870                     p_invoice_lines_rec.attribute11,
15871                     p_invoice_lines_rec.attribute12,
15872                     p_invoice_lines_rec.attribute13,
15873                     p_invoice_lines_rec.attribute14,
15874                     p_invoice_lines_rec.attribute15,
15875                     p_invoice_rec.attribute_category,
15876                     p_invoice_rec.attribute1,
15877                     p_invoice_rec.attribute2,
15878                     p_invoice_rec.attribute3,
15879                     p_invoice_rec.attribute4,
15880                     p_invoice_rec.attribute5,
15881                     p_invoice_rec.attribute6,
15882                     p_invoice_rec.attribute7,
15883                     p_invoice_rec.attribute8,
15884                     p_invoice_rec.attribute9,
15885                     p_invoice_rec.attribute10,
15886                     p_invoice_rec.attribute11,
15887                     p_invoice_rec.attribute12,
15888                     p_invoice_rec.attribute13,
15889                     p_invoice_rec.attribute14,
15890                     p_invoice_rec.attribute15,
15891                     p_invoice_lines_rec.partial_segments,
15892                     p_default_last_updated_by,
15893                     p_default_last_update_login,
15894                     p_calling_sequence,
15895                     l_award_id,
15896                     'AWARD_SET_ID_REMOVE' ) <> TRUE  THEN
15897           IF GMS_AP_API.gms_debug_switch(AP_IMPORT_INVOICES_PKG.g_debug_switch)
15898             THEN
15899             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15900               AP_IMPORT_UTILITIES_PKG.Print(
15901                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
15902                   '(v_check_line_project_info 3) Invalid GMS Info:Reject');
15903             END IF;
15904           END IF;
15905 
15906           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
15907                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
15908                  p_invoice_lines_rec.invoice_line_id,
15909                 'INSUFFICIENT GMS INFO',
15910                 p_default_last_updated_by,
15911                 p_default_last_update_login,
15912                 current_calling_sequence) <> TRUE) THEN
15913             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15914               AP_IMPORT_UTILITIES_PKG.Print(
15915                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
15916                   'insert_rejections<-'||current_calling_sequence);
15917             END IF;
15918              RAISE check_project_failure;
15919           END IF;
15920           --
15921           l_current_invoice_status := 'N';
15922         END IF; -- GMS
15923       END IF; -- l_current_invoice_Status ='Y' AND l_award_id is not null
15924 
15925       --------------------------------------------------------------
15926       -- Step 4
15927       -- IF flexbuild is successful THEN get ccid
15928       --------------------------------------------------------------
15929       -- IF ccid is created THEN fine
15930       -- Else get ccid from concat segments since it is new
15931       IF AP_IMPORT_INVOICES_PKG.g_source <> 'PPA'  THEN
15932           IF (l_current_invoice_status = 'Y') THEN
15933             IF (l_pa_default_dist_ccid = -1) THEN
15934               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
15935                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
15936                   '(v_check_line_project_info 4) Create new ccid from concat segs');
15937               END IF;
15938 
15939               -- Create new ccid
15940               -- IF creation fails THEN reject
15941               -- Bug 1414119 Changed operation from CREATE_COMBINATION to
15942               -- CREATE_COMB_NO_AT at all the places to avoid the autonomous
15943               -- transaction insert for new code combinations when dynamic
15944               -- insert is on.
15945               -- bug 2496185 by isartawi .. cache the code_combination_ids
15946 
15947               l_key := to_char(nvl(p_chart_of_accounts_id,0))||' '
15948                        ||l_pa_concatenated_segments||' '
15949                        ||to_char(AP_IMPORT_INVOICES_PKG.g_inv_sysdate,'dd-mm-yyyy');
15950               fnd_plsql_cache.generic_1tom_get_values(
15951                           AP_IMPORT_INVOICES_PKG.lg_many_controller1,
15952                           AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
15953                           l_key,
15954                           l_numof_values,
15955                           l_values,
15956                           l_ret_code);
15957 
15958               IF l_ret_code = '1' THEN --  means l_key found in cache
15959                 l_dist_code_combination_id := to_number(l_values(1).varchar2_1);
15960                 l_validate_res             := l_values(1).varchar2_2;
15961                 l_reason_unbuilt_flex      := l_values(1).varchar2_3;
15962 
15963               ELSE  -- IF l_key not found in cache .. cache it
15964            -- For BUG 3000219. Changed g_inv_sysdate to p_accounting_date
15965                 IF (fnd_flex_keyval.validate_segs(
15966                    'CREATE_COMB_NO_AT' ,
15967                    'SQLGL',
15968                    'GL#',
15969                    p_chart_of_accounts_id,
15970                    l_pa_concatenated_segments,
15971                    'V',
15972                    p_accounting_date,   --BUG 3000219.Changed from AP_IMPORT_INVOICES_PKG.g_inv_sysdate
15973                    'ALL',
15974                    NULL,
15975                    NULL,
15976                    'GL_global\\nSUMMARY_FLAG\\nI\\nAPPL=SQLAP;NAME=AP_ALL_PARENT_FLEX_NA\\nN',
15977                    NULL,
15978                    FALSE,
15979                    FALSE,
15980                    NULL,
15981                    NULL,
15982                    NULL,
15983                    NULL,
15984                    NULL,
15985                    NULL) <> TRUE) THEN
15986                   l_validate_res := 'FALSE';
15987                 ELSE
15988                   l_validate_res := 'TRUE';
15989                 END IF;
15990 
15991                 l_dist_code_combination_id := fnd_flex_keyval.combination_id;
15992                 l_reason_unbuilt_flex  := fnd_flex_keyval.error_message;
15993 
15994                 l_valueOut.varchar2_1 := to_char(l_dist_code_combination_id);
15995                 l_valueOut.varchar2_2 := l_validate_res;
15996                 l_valueOut.varchar2_3 := l_reason_unbuilt_flex;
15997                 l_values(1) := l_valueOut;
15998                 l_numof_values := 1;
15999 
16000                 fnd_plsql_cache.generic_1tom_put_values(
16001                             AP_IMPORT_INVOICES_PKG.lg_many_controller1,
16002                             AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
16003                             l_key,
16004                             l_numof_values,
16005                             l_values);
16006               END IF;
16007 
16008               IF (l_validate_res <> 'TRUE') THEN
16009                 --Invalid Creation combination
16010                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16011                   AP_IMPORT_UTILITIES_PKG.Print(
16012                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
16013                       '(v_check_line_project_info 4) Invalid ccid:Reject');
16014                 END IF;
16015 
16016                 IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16017                    AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16018                     p_invoice_lines_rec.invoice_line_id,
16019                     'INVALID PA ACCT',
16020                     p_default_last_updated_by,
16021                     p_default_last_update_login,
16022                     current_calling_sequence) <> TRUE) THEN
16023                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16024                     AP_IMPORT_UTILITIES_PKG.Print(
16025                       AP_IMPORT_INVOICES_PKG.g_debug_switch,
16026                         'insert_rejections<-'||current_calling_sequence);
16027                   END IF;
16028                    RAISE check_project_failure;
16029                 END IF;
16030                 --
16031                 l_current_invoice_status := 'N';
16032                 l_dist_code_combination_id := 0;
16033                 l_unbuilt_flex := l_pa_concatenated_segments;
16034               Else
16035                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16036                   AP_IMPORT_UTILITIES_PKG.Print(
16037                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
16038                   '(v_check_line_project_info 4) Valid ccid created for project');
16039                 END IF;
16040 
16041                 -- Valid Creation Combination
16042                 l_reason_unbuilt_flex := NULL;
16043                 l_unbuilt_flex := NULL;
16044 
16045               END IF; -- Validate res <> TRUE
16046 
16047               --
16048               -- show output values (only IF debug_switch = 'Y')
16049               --
16050               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16051                 AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16052                     '------------------>  l_dist_code_combination_id= '||
16053                 to_char(l_dist_code_combination_id)
16054                 ||' l_reason_unbuilt_flex = '||l_reason_unbuilt_flex
16055                 ||' l_unbuilt_flex = '||l_unbuilt_flex
16056                 ||' l_current_invoice_status = '||l_current_invoice_status);
16057               END IF;
16058 
16059             Else -- pa default ccid is valid
16060               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16061                 AP_IMPORT_UTILITIES_PKG.Print(
16062                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
16063                   '(v_check_line_project_info 5) Valid ccid from PA Flexbuild');
16064               END IF;
16065 
16066               l_dist_code_combination_id := l_pa_default_dist_ccid;
16067 
16068             END IF; --pa_default_ccid = -1
16069 
16070             --------------------------------------------------------------
16071             -- Step 5
16072             -- Return PA generated ccid to calling module for evaluation
16073             -- with overlay information.
16074             --------------------------------------------------------------
16075 
16076             -- Overlay will be done in check Account info
16077             --
16078             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16079               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16080              '(v_check_line_project_info 6) Set OUT parameter with PA ccid');
16081             END IF;
16082 
16083             p_pa_built_account := l_dist_code_combination_id;
16084           END IF; -- current_invoice_status(IF before l_pa_default_dist_ccid)
16085       END IF; -- source <> 'PPA'
16086     END IF; -- l_current_invoice_status( IF before pa_flexbuild)
16087 
16088   ELSE
16089     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16090       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16091         '(v_check_line_project_info) No Project Id');
16092     END IF;
16093   END IF; -- PA Info
16094 
16095   p_current_invoice_status := l_current_invoice_status;
16096 
16097   RETURN (TRUE);
16098 
16099 EXCEPTION
16100   WHEN OTHERS THEN
16101     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16102       AP_IMPORT_UTILITIES_PKG.Print(
16103         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16104     END IF;
16105 
16106     IF (SQLCODE < 0) THEN
16107       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16108         AP_IMPORT_UTILITIES_PKG.Print(
16109           AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
16110       END IF;
16111     END IF;
16112     RETURN(FALSE);
16113 
16114 END v_check_line_project_info;
16115 
16116 
16117 ------------------------------------------------------------------------------
16118 -- This function is used to validate line level accounting information.
16119 --
16120 ------------------------------------------------------------------------------
16121 FUNCTION v_check_line_account_info (
16122    p_invoice_lines_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
16123    p_freight_code_combination_id  IN            NUMBER,
16124    p_pa_built_account             IN            NUMBER,
16125    p_accounting_date              IN            DATE,
16126    p_set_of_books_id              IN            NUMBER,
16127    p_chart_of_accounts_id         IN            NUMBER,
16128    p_default_last_updated_by      IN            NUMBER,
16129    p_default_last_update_login    IN            NUMBER,
16130    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
16131    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
16132 IS
16133    check_account_failure          EXCEPTION;
16134    l_current_invoice_status          VARCHAR2(1) := 'Y';
16135    l_valid_dist_code              VARCHAR(1);
16136    l_dist_code_combination_id      NUMBER;
16137    l_overlayed_ccid               NUMBER;
16138    l_catsegs                      VARCHAR2(200);
16139    l_unbuilt_flex                 VARCHAR2(240):='';
16140    l_reason_unbuilt_flex          VARCHAR2(2000):='';
16141    l_key                          VARCHAR2(1000);
16142    l_numof_values                   NUMBER;
16143    l_valueOut                   fnd_plsql_cache.generic_cache_value_type;
16144    l_values                     fnd_plsql_cache.generic_cache_values_type;
16145    l_ret_code                       VARCHAR2(1);
16146    l_validate_res                 VARCHAR2(10);
16147    current_calling_sequence        VARCHAR2(2000);
16148    debug_info                     VARCHAR2(500);
16149 
16150 BEGIN
16151   -- Update the calling sequence
16152   --
16153   current_calling_sequence :=
16154        'AP_IMPORT_VALIDATION_PKG.v_check_line_account_info<-'
16155        ||P_calling_sequence;
16156 
16157   l_dist_code_combination_id :=
16158     nvl(p_invoice_lines_rec.dist_code_combination_id, p_pa_built_account);
16159   -----------------------------------------------------------
16160   -- Step 1. Initialize account to freight system account if
16161   -- line is of type FREIGHT and no ccid was provided for it
16162   -- either as a default ccid or through projects.
16163   -----------------------------------------------------------
16164   debug_info := '(v_check_line_account_info 1) '||
16165                  'Check IF item line doesnt have account info';
16166 
16167   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16168     AP_IMPORT_UTILITIES_PKG.Print(
16169      AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16170   END IF;
16171 
16172   --Assigning system freight account if no freight account is specified
16173   --Change made for bug#2709960
16174   IF (p_invoice_lines_rec.line_type_lookup_code = 'FREIGHT' AND
16175       l_dist_code_combination_id is NULL) THEN
16176     l_dist_code_combination_id := p_freight_code_combination_id;
16177     p_invoice_lines_rec.dist_code_combination_id :=
16178                                   p_freight_code_combination_id;
16179   END IF;
16180 
16181   ------------------------------------------------------------------------
16182   -- Step 2. Performs several checks if line did not provide distribution
16183   --         set as source.
16184   -- a. Validate account (source of account is line code combination id
16185   --    or pa_built_account) with overlay information if account is not
16186   --    null or concatenated segments on the line are a partial set
16187   --    but only if line is either not project related or projects allows
16188   --    account override.  Do not reject if the account (source of account
16189   --    was line code combination id or pa_built_account) is null and the
16190   --    concatenated segments was a partial set.
16191   -- b. Validate account if concatenated segments is a full set and account
16192   --    was null.  Obtain ccid from cache and validate it.  Also, if other
16193   --    overlay information was provided verify that it generates a valid
16194   --    account.
16195   ------------------------------------------------------------------------
16196   IF ((p_invoice_lines_rec.distribution_set_id is NULL AND
16197        p_invoice_lines_rec.distribution_set_name is null)) THEN
16198 
16199      /*  Overlay lines before we validate in
16200         case the base Code Combination is invalid, but the overlay
16201         Code Combination is not.  */
16202 
16203     IF ((l_dist_code_combination_id IS NOT NULL OR
16204      (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL AND
16205           p_invoice_lines_rec.partial_segments <> 'N')) AND
16206         (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL  OR
16207          p_invoice_lines_rec.balancing_segment      IS NOT NULL  OR
16208          p_invoice_lines_rec.cost_center_segment    IS NOT NULL  OR
16209          p_invoice_lines_rec.account_segment        IS NOT NULL) AND
16210         (p_invoice_lines_rec.project_id IS NULL OR
16211      (p_invoice_lines_rec.project_id IS NOT NULL AND
16212       AP_IMPORT_INVOICES_PKG.g_pa_allows_overrides = 'Y'))) THEN
16213 
16214           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16215             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16216               '(v_check_line_account_info 2) '
16217               || 'Check Overlay Segments for line');
16218           END IF;
16219 
16220           l_overlayed_ccid := l_dist_code_combination_id;
16221 
16222       IF (AP_UTILITIES_PKG.overlay_segments
16223             (p_invoice_lines_rec.balancing_segment,
16224              p_invoice_lines_rec.cost_center_segment,
16225              p_invoice_lines_rec.account_segment,
16226              p_invoice_lines_rec.dist_code_concatenated,
16227              l_overlayed_ccid ,                 -- IN OUT NOCOPY
16228              p_set_of_books_id ,
16229              'CREATE_COMB_NO_AT',    -- Overlay Mode
16230              l_unbuilt_flex ,                           -- OUT NOCOPY
16231              l_reason_unbuilt_flex ,                    -- OUT NOCOPY
16232              FND_GLOBAL.RESP_APPL_ID,
16233              FND_GLOBAL.RESP_ID,
16234              FND_GLOBAL.USER_ID,
16235              current_calling_sequence ) <> TRUE) THEN
16236 
16237         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16238           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16239             '(v_check_line_account_info 2) '||
16240             'Overlay_Segments<-'||current_calling_sequence);
16241         END IF;
16242         -- Bug 6124714
16243 		-- Raise check_account_failure;
16244 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16245               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16246               p_invoice_lines_rec.invoice_line_id,
16247              'INVALID DISTRIBUTION ACCT',
16248                 p_default_last_updated_by,
16249               p_default_last_update_login,
16250                current_calling_sequence) <> TRUE) THEN
16251 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16252                 AP_IMPORT_UTILITIES_PKG.Print(
16253                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
16254                   'insert_rejections<-'||
16255                    current_calling_sequence);
16256 			END IF;
16257 			RAISE check_account_failure;
16258         END IF; -- insert rejections
16259       ELSE -- overlay segs
16260 
16261         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16262           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16263            '------------------> l_unbuilt_flex = '||
16264                   l_unbuilt_flex||'l_reason_unbuilt_flex = '||
16265                   l_reason_unbuilt_flex||'l_overlayed_ccid = '||
16266                   to_char(l_overlayed_ccid));
16267         END IF;
16268 
16269         IF (l_overlayed_ccid = -1 AND
16270         l_dist_code_combination_id IS NOT NULL) THEN
16271           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16272         AP_IMPORT_UTILITIES_PKG.Print(
16273            AP_IMPORT_INVOICES_PKG.g_debug_switch,
16274                '(v_check_line_account_info 2)' ||
16275                ' Invalid dist_code_combination_id overlay');
16276           END IF;
16277           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16278                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16279                p_invoice_lines_rec.invoice_line_id,
16280                'INVALID ACCT OVERLAY',
16281                p_default_last_updated_by,
16282                p_default_last_update_login,
16283                current_calling_sequence) <> TRUE) THEN
16284             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16285               AP_IMPORT_UTILITIES_PKG.Print(
16286                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
16287                   'insert_rejections<-'
16288                  || current_calling_sequence);
16289             END IF;
16290             RAISE check_account_failure;
16291              --
16292           END IF; -- insert rejections
16293           l_current_invoice_status := 'N';
16294         ELSE -- overlayed_ccid <> -1
16295           BEGIN
16296             SELECT 'X'
16297               INTO l_valid_dist_code
16298               FROM gl_code_combinations
16299              WHERE code_combination_id = l_overlayed_ccid
16300                AND enabled_flag='Y'
16301                AND NVL(END_date_active, p_accounting_date) --Bug 2923286 Changed gl_inv_sysdate to p_accounting_date
16302                    >= p_accounting_date
16303                AND NVL(start_date_active, p_accounting_date)
16304                    <= p_accounting_date;
16305           EXCEPTION
16306             WHEN NO_DATA_FOUND THEN
16307               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16308                 AP_IMPORT_UTILITIES_PKG.Print(
16309                    AP_IMPORT_INVOICES_PKG.g_debug_switch,
16310                    '(v_check_line_account_info 4) '||
16311                    ' Invalid overlayed ccid ');
16312               END IF;
16313 
16314               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16315                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16316                     p_invoice_lines_rec.invoice_line_id,
16317                   'INVALID DISTRIBUTION ACCT',
16318                      p_default_last_updated_by,
16319                    p_default_last_update_login,
16320                     current_calling_sequence) <> TRUE) THEN
16321                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16322                   AP_IMPORT_UTILITIES_PKG.Print(
16323                     AP_IMPORT_INVOICES_PKG.g_debug_switch,
16324                     'insert_rejections<-'
16325                    ||current_calling_sequence);
16326                 END IF;
16327                  RAISE check_account_failure;
16328               END IF; -- insert rejections
16329               --
16330               l_current_invoice_status := 'N';
16331           END;
16332 
16333         END IF; -- l_dist_code_combination_id is -1
16334       END IF; --overlay segments
16335 
16336     ELSIF (l_dist_code_combination_id IS NULL AND
16337            p_invoice_lines_rec.dist_code_concatenated IS NOT NULL AND
16338            p_invoice_lines_rec.partial_segments = 'N' AND
16339            p_invoice_lines_rec.po_number IS NULL AND
16340            p_invoice_lines_rec.po_header_id IS NULL) THEN
16341 
16342       -- bug 2496185 by isartawi .. cache the code_combination_ids
16343       l_key := TO_CHAR(NVL(p_chart_of_accounts_id,0))||' '||
16344                p_invoice_lines_rec.dist_code_concatenated||' '||
16345            to_char(p_accounting_date,'dd-mm-yyyy');
16346 
16347       fnd_plsql_cache.generic_1tom_get_values(
16348                AP_IMPORT_INVOICES_PKG.lg_many_controller1,
16349                AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
16350                l_key,
16351                l_numof_values,
16352                l_values,
16353                l_ret_code);
16354       IF l_ret_code = '1' THEN --  means l_key found in cache
16355         l_dist_code_combination_id := to_number(l_values(1).varchar2_1);
16356         l_validate_res             := l_values(1).varchar2_2;
16357          -- Bug 5533471
16358         p_invoice_lines_rec.dist_code_combination_id := l_dist_code_combination_id;
16359 
16360       ELSE  -- IF l_key not found in cache .. cache it
16361         IF (fnd_flex_keyval.validate_segs
16362                 ('CREATE_COMB_NO_AT' ,   --Bug6624362
16363                  'SQLGL',
16364                  'GL#',
16365                  p_chart_of_accounts_id,
16366                  p_invoice_lines_rec.dist_code_concatenated,
16367                  'V',
16368                  p_accounting_date,
16369                  'ALL',
16370                  NULL,
16371                  '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
16372                  'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
16373                  NULL,
16374                  NULL,
16375                  FALSE,
16376                  FALSE,
16377                  FND_GLOBAL.RESP_APPL_ID,
16378                  FND_GLOBAL.RESP_ID,
16379                  FND_GLOBAL.USER_ID) <> TRUE) THEN
16380           l_validate_res := 'FALSE';
16381         ELSE --validate_segs
16382           l_validate_res := 'TRUE';
16383         END IF;
16384         l_dist_code_combination_id := fnd_flex_keyval.combination_id;
16385         l_valueOut.varchar2_1      := to_char(l_dist_code_combination_id);
16386         l_valueOut.varchar2_2      := l_validate_res;
16387         l_values(1)                := l_valueOut;
16388         l_numof_values             := 1;
16389 
16390         fnd_plsql_cache.generic_1tom_put_values(
16391                   AP_IMPORT_INVOICES_PKG.lg_many_controller1,
16392                   AP_IMPORT_INVOICES_PKG.lg_generic_storage1,
16393                   l_key,
16394                   l_numof_values,
16395                   l_values);
16396       END IF; -- l_ret_code='1'
16397 
16398        -- Bug 5533471
16399       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16400           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16401             'l_dist_code_combination_id: '|| l_dist_code_combination_id
16402            ||', l_validate_res: '||l_validate_res);
16403       END IF;
16404 
16405       IF (l_validate_res <> 'TRUE')  THEN
16406         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16407           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16408             '(v_check_line_account_info 2) '||
16409             'Invalid dist_code_concatenated ');
16410           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16411             '(v_check_line_account_info 2) '||
16412             'Error create account infomation : '||
16413             FND_FLEX_KEYVAL.error_message);
16414         END IF;
16415 
16416         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16417               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16418               p_invoice_lines_rec.invoice_line_id,
16419              'INVALID DISTRIBUTION ACCT',
16420                 p_default_last_updated_by,
16421               p_default_last_update_login,
16422                current_calling_sequence) <> TRUE) THEN
16423           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16424                 AP_IMPORT_UTILITIES_PKG.Print(
16425                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
16426                   'insert_rejections<-'||
16427                    current_calling_sequence);
16428           END IF;
16429           RAISE check_account_failure;
16430         END IF; -- insert rejections
16431         --
16432         l_current_invoice_status := 'N';
16433 
16434       ELSE -- validate res is TRUE
16435         IF ((l_current_invoice_status <> 'N') AND
16436             ((p_invoice_lines_rec.balancing_segment IS NOT NULL) OR
16437           (p_invoice_lines_rec.cost_center_segment IS NOT NULL) OR
16438          (p_invoice_lines_rec.account_segment IS NOT NULL))) THEN
16439           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16440                 AP_IMPORT_UTILITIES_PKG.Print(
16441                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
16442                       '(v_check_line_account_info 2) '||
16443                       'Check Overlay Segments for dist_code_concatenated ');
16444           END IF;
16445 
16446           l_overlayed_ccid := l_dist_code_combination_id;
16447 
16448           IF (AP_UTILITIES_PKG.overlay_segments(
16449                   p_invoice_lines_rec.balancing_segment,
16450                   p_invoice_lines_rec.cost_center_segment,
16451                   p_invoice_lines_rec.account_segment,
16452                   NULL,
16453                   l_overlayed_ccid ,                     -- IN OUT NOCOPY
16454                   p_set_of_books_id ,
16455                   'CREATE_COMB_NO_AT' , -- Overlay Mode
16456                   l_unbuilt_flex ,                       -- OUT NOCOPY
16457                   l_reason_unbuilt_flex ,                -- OUT NOCOPY
16458                   FND_GLOBAL.RESP_APPL_ID,
16459                   FND_GLOBAL.RESP_ID,
16460                   FND_GLOBAL.USER_ID,
16461                   current_calling_sequence,
16462                   Null ) <> TRUE) THEN
16463             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16464                  AP_IMPORT_UTILITIES_PKG.Print(
16465                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
16466                 '(v_check_line_account_info 2) '||
16467                 ' Overlay_Segments<-'||current_calling_sequence);
16468             END IF;
16469             -- Bug 6124714
16470 		    -- Raise check_account_failure;
16471 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16472               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16473               p_invoice_lines_rec.invoice_line_id,
16474              'INVALID DISTRIBUTION ACCT',
16475                 p_default_last_updated_by,
16476               p_default_last_update_login,
16477                current_calling_sequence) <> TRUE) THEN
16478 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16479                 AP_IMPORT_UTILITIES_PKG.Print(
16480                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
16481                   'insert_rejections<-'||
16482                    current_calling_sequence);
16483 			END IF;
16484 			RAISE check_account_failure;
16485         END IF; -- insert rejections
16486 
16487           ELSE -- overlay segs
16488             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16489                   AP_IMPORT_UTILITIES_PKG.Print(
16490                   AP_IMPORT_INVOICES_PKG.g_debug_switch,
16491                   '-----------------> l_unbuilt_flex = '||
16492                   l_unbuilt_flex||' l_reason_unbuilt_flex = '||
16493                   l_reason_unbuilt_flex||'l_overlayed_ccid: '||
16494                   to_char(l_overlayed_ccid));
16495             END IF;
16496 
16497             IF (l_overlayed_ccid = -1) THEN
16498               IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16499                 AP_IMPORT_UTILITIES_PKG.Print(
16500                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
16501                  '(v_check_line_account_info 4) '||
16502                  'Invalid dist_code_combination_id  overlay');
16503               END IF;
16504 
16505               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16506                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16507                    p_invoice_lines_rec.invoice_line_id,
16508                   'INVALID ACCT OVERLAY',
16509                    p_default_last_updated_by,
16510                    p_default_last_update_login,
16511                     current_calling_sequence) <> TRUE) THEN
16512                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16513                   AP_IMPORT_UTILITIES_PKG.Print(
16514                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16515                        'insert_rejections<-'||
16516                      current_calling_sequence);
16517                 END IF;
16518                 RAISE check_account_failure;
16519               END IF; -- insert rejections
16520               l_current_invoice_status := 'N';
16521             END IF; -- overlayed dist code combination id is -1
16522           END IF; --overlay segments
16523 
16524         -- Bug 5533471
16525         ELSIF  ((l_current_invoice_status <> 'N')
16526                 AND (l_dist_code_combination_id = -1))  THEN
16527 
16528           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16529                 AP_IMPORT_UTILITIES_PKG.Print(
16530                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
16531                  '(v_check_line_account_info 4.1) '||
16532                  'Invalid dist_code_combination_id  overlay');
16533           END IF;
16534 
16535           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16536                   AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16537                    p_invoice_lines_rec.invoice_line_id,
16538                   'INVALID ACCT OVERLAY',
16539                    p_default_last_updated_by,
16540                    p_default_last_update_login,
16541                     current_calling_sequence) <> TRUE) THEN
16542             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16543                   AP_IMPORT_UTILITIES_PKG.Print(
16544                      AP_IMPORT_INVOICES_PKG.g_debug_switch,
16545                        'insert_rejections<-'||
16546                      current_calling_sequence);
16547             END IF;
16548                 RAISE check_account_failure;
16549           END IF; -- insert rejections
16550           l_current_invoice_status := 'N';
16551 
16552          -- Bug 5533471
16553         ELSIF  ((l_current_invoice_status <> 'N')
16554                 AND (l_dist_code_combination_id <> -1))  THEN
16555 
16556           p_invoice_lines_rec.dist_code_combination_id := l_dist_code_combination_id;
16557 
16558         END IF; -- Invoice Status
16559       END IF; -- Validate res
16560     END IF; -- accounting information exists
16561   END IF; -- distribution set id is null
16562 
16563   ------------------------------------------------------------------
16564   -- Step 3. Validate account information relative to po and receipt
16565   ------------------------------------------------------------------
16566   -- Made changes to the following stmt for receipt matching project
16567   -- We should NOT reject a non-item line IF it has account information,
16568   -- po information and receipt information.
16569   -- But we should Reject IF it has acct info, po info and no receipt info.
16570  -- Bug 7487507
16571  -- Changed the paranthesis in the If condition
16572     IF ((p_invoice_lines_rec.line_type_lookup_code <> 'ITEM' AND
16573        (p_invoice_lines_rec.distribution_set_id IS NOT NULL OR
16574         p_invoice_lines_rec.distribution_set_name IS NOT NULL) AND
16575        (l_dist_code_combination_id IS NOT NULL OR l_overlayed_ccid IS NOT NULL))
16576 OR
16577       ((p_invoice_lines_rec.line_type_lookup_code <> 'ITEM')  AND
16578        ((p_invoice_lines_rec.po_header_id is not null) OR
16579         (p_invoice_lines_rec.po_number is not null)) AND
16580        ((p_invoice_lines_rec.receipt_number is null) AND
16581         (p_invoice_lines_rec.rcv_transaction_id is null)))   OR
16582        (((p_invoice_lines_rec.po_header_id is NOT NULL) OR
16583          (p_invoice_lines_rec.po_number IS NOT NULL)) AND
16584         ((p_invoice_lines_rec.distribution_set_id is NOT NULL) OR
16585          (p_invoice_lines_rec.distribution_set_name is NOT NULL))) ) THEN
16586     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16587       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16588         '(v_check_line_account_info 3) '||
16589         'Inconsistent dist Info ');
16590     END IF;
16591 
16592     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16593         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16594         p_invoice_lines_rec.invoice_line_id,
16595         'INCONSISTENT DIST INFO',
16596         p_default_last_updated_by,
16597         p_default_last_update_login,
16598         current_calling_sequence) <> TRUE) THEN
16599       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16600         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16601           'insert_rejections<-'||
16602           current_calling_sequence);
16603       END IF;
16604       RAISE check_account_failure;
16605     END IF; -- insert rejections
16606     l_current_invoice_status := 'N';
16607   END IF; -- Step 3
16608 
16609   -------------------------------------------------------------------------
16610   -- Step 4. Validate account
16611   -------------------------------------------------------------------------
16612   debug_info := '(v_check_line_account_info 4) calling parent validation ';
16613   IF ((l_dist_code_combination_id is not NULL AND
16614        l_dist_code_combination_id <> -1)          OR
16615       (l_overlayed_ccid IS NOT NULL AND l_overlayed_ccid <> -1))  THEN
16616     debug_info := '(v_check_line_account_info 4) Inside parent validation';
16617     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16618       AP_IMPORT_UTILITIES_PKG.Print(
16619         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
16620     END IF;
16621     IF (l_overlayed_ccid IS NULL OR l_overlayed_ccid = -1) THEN
16622       l_overlayed_ccid := l_dist_code_combination_id;
16623     END IF;
16624     IF fnd_flex_keyval.validate_ccid(
16625        appl_short_name => 'SQLGL',
16626        key_flex_code => 'GL#',
16627        structure_number => p_chart_of_accounts_id,
16628        combination_id => l_overlayed_ccid) THEN
16629       l_catsegs := fnd_flex_keyval.concatenated_values;
16630 
16631       IF (fnd_flex_keyval.validate_segs(
16632                         'CHECK_COMBINATION',
16633                         'SQLGL',
16634                         'GL#',
16635                         p_chart_of_accounts_id,
16636                         l_catsegs,
16637                         'V',
16638                         p_accounting_date,
16639                         'ALL',
16640                         NULL,
16641                         '\nSUMMARY_FLAG\nI\nAPPL=SQLGL;' ||
16642                         'NAME=GL_CTAX_SUMMARY_ACCOUNT\nN',
16643                         NULL,
16644                         NULL,
16645                         FALSE,
16646                         FALSE,
16647                         FND_GLOBAL.RESP_APPL_ID,
16648                         FND_GLOBAL.RESP_ID,
16649                         FND_GLOBAL.USER_ID)<>TRUE)  THEN
16650         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16651               AP_IMPORT_UTILITIES_PKG.Print(
16652               AP_IMPORT_INVOICES_PKG.g_debug_switch,
16653                   '((v_check_line_account_info 4) - '||
16654                   ' Invalid Code Combination id');
16655         END IF;
16656         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16657               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16658                p_invoice_lines_rec.invoice_line_id,
16659               'INVALID DISTRIBUTION ACCT',
16660                p_default_last_updated_by,
16661                p_default_last_update_login,
16662                current_calling_sequence) <> TRUE) THEN
16663           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16664             AP_IMPORT_UTILITIES_PKG.Print(
16665           AP_IMPORT_INVOICES_PKG.g_debug_switch,
16666                   'insert_rejections<-'||
16667                   current_calling_sequence);
16668           END IF;
16669           RAISE check_account_failure;
16670         END IF; -- insert rejections
16671         l_current_invoice_status := 'N';
16672       END IF; -- validate segments
16673     ELSE -- Validate ccid
16674       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16675         AP_IMPORT_UTILITIES_PKG.Print(
16676         AP_IMPORT_INVOICES_PKG.g_debug_switch,
16677                 '((v_check_line_account_info 4) - '||
16678                 ' Invalid Code Combination id');
16679       END IF;
16680       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16681              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16682               p_invoice_lines_rec.invoice_line_id,
16683              'INVALID DISTRIBUTION ACCT',
16684               p_default_last_updated_by,
16685               p_default_last_update_login,
16686               current_calling_sequence) <> TRUE) THEN
16687         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16688              AP_IMPORT_UTILITIES_PKG.Print(
16689              AP_IMPORT_INVOICES_PKG.g_debug_switch,
16690                    'insert_rejections<-'||
16691                    current_calling_sequence);
16692         END IF;
16693         RAISE check_account_failure;
16694       END IF; -- insert rejections
16695       l_current_invoice_status := 'N';
16696     END IF; -- Validate ccid
16697   END IF; -- either dist ccid or overlayed ccid are not null
16698 
16699   -- Return value
16700   p_current_invoice_status := l_current_invoice_status;
16701 
16702   RETURN (TRUE);
16703 
16704 
16705 EXCEPTION
16706   WHEN OTHERS THEN
16707     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16708       AP_IMPORT_UTILITIES_PKG.Print(
16709         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
16710     END IF;
16711 
16712     IF (SQLCODE < 0) THEN
16713       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16714         AP_IMPORT_UTILITIES_PKG.Print(
16715           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
16716       END IF;
16717     END IF;
16718 RETURN(FALSE);
16719 
16720 END v_check_line_account_info;
16721 
16722 
16723 
16724 
16725 -----------------------------------------------------------------------------
16726 -- This function is used to validate line level deferred accounting
16727 -- information.
16728 -----------------------------------------------------------------------------
16729 FUNCTION v_check_deferred_accounting (
16730          p_invoice_lines_rec
16731            IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
16732          p_set_of_books_id              IN            NUMBER,
16733          p_default_last_updated_by      IN            NUMBER,
16734          p_default_last_update_login    IN            NUMBER,
16735          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
16736          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
16737 
16738 IS
16739 
16740 check_defer_acctg_failure      EXCEPTION;
16741 l_period_name                  VARCHAR2(15);
16742 l_valid_period_type           VARCHAR2(30);
16743 l_current_invoice_status      VARCHAR2(1) := 'Y';
16744 current_calling_sequence        VARCHAR2(2000);
16745 debug_info                     VARCHAR2(500);
16746 
16747 BEGIN
16748   -- Update the calling sequence
16749   --
16750   current_calling_sequence :=
16751     'AP_IMPORT_VALIDATION_PKG.v_check_deferred_accounting<-'
16752     ||P_calling_sequence;
16753 
16754   ----------------------------------------------------------------------------
16755   --Step 1 - Validate the deferred accounting flag.  Value should be either
16756   -- Null, N or Y.
16757   --
16758   ----------------------------------------------------------------------------
16759   IF (((nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') <> 'N')  AND
16760        (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'Y') <> 'Y')) OR
16761       ((nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'N') AND
16762        (p_invoice_lines_rec.def_acctg_start_date IS NOT NULL OR
16763         p_invoice_lines_rec.def_acctg_end_date IS NOT NULL OR
16764         p_invoice_lines_rec.def_acctg_number_of_periods IS NOT NULL OR
16765         p_invoice_lines_rec.def_acctg_period_type IS NOT NULL))) THEN
16766     debug_info := '(Check_deferred_accounting 1)Validate appropriate def data';
16767     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16768       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16769                                     debug_info);
16770     END IF;
16771 
16772     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16773         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16774         p_invoice_lines_rec.invoice_line_id,
16775         'INVALID DEFERRED FLAG',
16776         p_default_last_updated_by,
16777         p_default_last_update_login,
16778         current_calling_sequence) <> TRUE) THEN
16779       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16780         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16781           'insert_rejections<-'||current_calling_sequence);
16782       END IF;
16783       RAISE check_defer_acctg_failure;
16784     END IF;
16785     l_current_invoice_status := 'N';
16786   END IF;
16787 
16788   ----------------------------------------------------------------------------
16789   -- Step 2 - Validate that mandatory deferred accounting data is populated if
16790   -- deferred accounting is requested.
16791   -- Also validate that if start date is populated it falls in an open period
16792   -- which is the same period as the period for the line.
16793   --
16794   -----------------------------------------------------------------------------
16795   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y') then
16796     debug_info := '(Check_deferred_accounting 2) Validate start date';
16797     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16798       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16799                                     debug_info);
16800     END IF;
16801 
16802     IF (p_invoice_lines_rec.def_acctg_start_date IS NULL OR
16803     (p_invoice_lines_rec.def_acctg_number_of_periods IS NULL AND
16804          p_invoice_lines_rec.def_acctg_end_date IS NULL)) THEN
16805       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16806             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16807             p_invoice_lines_rec.invoice_line_id,
16808             'INCOMPLETE DEF ACCTG INFO',
16809             p_default_last_updated_by,
16810             p_default_last_update_login,
16811             current_calling_sequence) <> TRUE) THEN
16812         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16813           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16814            'insert_rejections<-'||current_calling_sequence);
16815         END IF;
16816         RAISE check_defer_acctg_failure;
16817       END IF;
16818       l_current_invoice_status := 'N';
16819     END IF;
16820 
16821     IF (p_invoice_lines_rec.def_acctg_start_date IS NOT NULL) THEN
16822       BEGIN
16823         SELECT period_name
16824           INTO l_period_name
16825           FROM gl_period_statuses
16826          WHERE application_id = 200
16827            AND set_of_books_id = p_set_of_books_id
16828            AND trunc(p_invoice_lines_rec.def_acctg_start_date)
16829                between start_date and end_date
16830            AND closing_status in ('O', 'F')
16831            AND NVL(adjustment_period_flag, 'N') = 'N';
16832 
16833         IF (l_period_name <> p_invoice_lines_rec.period_name) then
16834           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16835             AP_IMPORT_UTILITIES_PKG.Print(
16836                AP_IMPORT_INVOICES_PKG.g_debug_switch,
16837                'Def Acctg Start Date is not is same period as line');
16838           END IF;
16839 
16840           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16841                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16842                p_invoice_lines_rec.invoice_line_id,
16843                'INVALID DEF START DATE',
16844                p_default_last_updated_by,
16845                p_default_last_update_login,
16846                current_calling_sequence) <> TRUE) THEN
16847             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16848               AP_IMPORT_UTILITIES_PKG.Print(
16849                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
16850                 'insert_rejections<-'||current_calling_sequence);
16851             END IF;
16852             RAISE check_defer_acctg_failure;
16853           END IF;
16854           l_current_invoice_status := 'N';
16855         END IF; -- period name is other than line period name
16856 
16857       EXCEPTION
16858         WHEN NO_DATA_FOUND then
16859           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16860             AP_IMPORT_UTILITIES_PKG.Print(
16861               AP_IMPORT_INVOICES_PKG.g_debug_switch,
16862               'Def Acctg Start Date is not in open period');
16863           END IF;
16864 
16865           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16866                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16867                p_invoice_lines_rec.invoice_line_id,
16868                'INVALID DEF START DATE',
16869                p_default_last_updated_by,
16870                p_default_last_update_login,
16871                current_calling_sequence) <> TRUE) THEN
16872             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16873               AP_IMPORT_UTILITIES_PKG.Print(
16874                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
16875                   'insert_rejections<-'||current_calling_sequence);
16876             END IF;
16877             RAISE check_defer_acctg_failure;
16878           END IF;
16879           l_current_invoice_status := 'N';
16880       END;
16881     END IF; -- def acctg start date is not null
16882 
16883   END IF; -- step 2
16884 
16885   ----------------------------------------------------------------------------
16886   -- Step 3 - Validate that the end date is larger than start date if the
16887   -- deferred flag is Y and the start date is not null.
16888   --
16889   -----------------------------------------------------------------------------
16890   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y' AND
16891       p_invoice_lines_rec.def_acctg_start_date is not null AND
16892       p_invoice_lines_rec.def_acctg_end_date is not null) then
16893     debug_info := '(Check_deferred_accounting 3) Validate end date';
16894     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16895       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16896                                     debug_info);
16897     END IF;
16898 
16899     IF (trunc(p_invoice_lines_rec.def_acctg_start_date) >
16900         trunc(p_invoice_lines_rec.def_acctg_end_date)) then
16901       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16902           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16903           p_invoice_lines_rec.invoice_line_id,
16904           'INVALID DEF END DATE',
16905           p_default_last_updated_by,
16906           p_default_last_update_login,
16907           current_calling_sequence) <> TRUE) THEN
16908         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16909             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16910             'insert_rejections<-'||current_calling_sequence);
16911         END IF;
16912         RAISE check_defer_acctg_failure;
16913       END IF;
16914       l_current_invoice_status := 'N';
16915     END IF;
16916   END IF; -- Deferred flag is Y and both start date and end dates are not null
16917 
16918   ---------------------------------------------------------------------------
16919   -- Step 4 - Validate that Number of periods is a positive integer and
16920   -- Populated if period type is populated but only if deferred flag is Y.
16921   --
16922   ---------------------------------------------------------------------------
16923   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y' AND
16924       p_invoice_lines_rec.def_acctg_period_type IS NOT NULL) THEN
16925     debug_info := '(Check_deferred_accounting 4) Validate number of periods';
16926     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16927       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16928                               debug_info);
16929     END IF;
16930 
16931     IF (p_invoice_lines_rec.def_acctg_number_of_periods is NULL OR
16932         p_invoice_lines_rec.def_acctg_number_of_periods < 0 OR
16933         floor(p_invoice_lines_rec.def_acctg_number_of_periods) <>
16934         ceil(p_invoice_lines_rec.def_acctg_number_of_periods)) THEN
16935       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16936           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16937           p_invoice_lines_rec.invoice_line_id,
16938           'INVALID DEF NUM OF PER',
16939           p_default_last_updated_by,
16940           p_default_last_update_login,
16941           current_calling_sequence) <> TRUE) THEN
16942         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16943           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16944           'insert_rejections<-'||current_calling_sequence);
16945         END IF;
16946         RAISE check_defer_acctg_failure;
16947       END IF;
16948       l_current_invoice_status := 'N';
16949 
16950     END IF;
16951 
16952     BEGIN
16953       SELECT 'Valid Period Type'
16954         INTO l_valid_period_type
16955         FROM xla_lookups
16956        WHERE lookup_type = 'XLA_DEFERRED_PERIOD_TYPE'
16957     AND lookup_code = p_invoice_lines_rec.def_acctg_period_type;
16958 
16959     EXCEPTION
16960       When NO_DATA_FOUND THEN
16961         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16962               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16963               p_invoice_lines_rec.invoice_line_id,
16964               'INVALID DEF PER TYPE',
16965               p_default_last_updated_by,
16966               p_default_last_update_login,
16967               current_calling_sequence) <> TRUE) THEN
16968           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
16969         AP_IMPORT_UTILITIES_PKG.Print(
16970            AP_IMPORT_INVOICES_PKG.g_debug_switch,
16971                    'insert_rejections<-'||current_calling_sequence);
16972           END IF;
16973           RAISE check_defer_acctg_failure;
16974         END IF;
16975         l_current_invoice_status := 'N';
16976 
16977     END;
16978   END IF; -- Deferred flag is Y and period type is populated.
16979 
16980   ---------------------------------------------------------------------------
16981  -- Step 5 - Validate that Period Type is populated if number of periods is
16982  -- Populated.  Also validate that it contains a valid type and that it is
16983  -- Not simulatneously populated with end date.
16984   --
16985   ---------------------------------------------------------------------------
16986   IF (nvl(p_invoice_lines_rec.deferred_acctg_flag, 'N') = 'Y' AND
16987       p_invoice_lines_rec.def_acctg_number_of_periods IS NOT NULL) THEN
16988     debug_info := '(Check_deferred_accounting 5) Validate period type';
16989     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
16990       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
16991                                     debug_info);
16992     End if;
16993 
16994     IF (p_invoice_lines_rec.def_acctg_period_type IS NULL OR
16995         (p_invoice_lines_rec.def_acctg_period_type IS NOT NULL AND
16996          p_invoice_lines_rec.def_acctg_end_date IS NOT NULL)) THEN
16997       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
16998            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
16999            p_invoice_lines_rec.invoice_line_id,
17000            'INVALID DEF PER TYPE',
17001            p_default_last_updated_by,
17002            p_default_last_update_login,
17003            current_calling_sequence) <> TRUE) THEN
17004         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
17005           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17006           'insert_rejections<-'||current_calling_sequence);
17007         END IF;
17008         RAISE check_defer_acctg_failure;
17009       END IF;
17010       l_current_invoice_status := 'N';
17011 
17012     END IF; -- period type is null or
17013             -- it is not null and end date is also not null
17014 
17015   END IF; -- deferred flag is Y and number of periods is populated
17016 
17017   --
17018   -- Return value
17019   p_current_invoice_status := l_current_invoice_status;
17020   RETURN (TRUE);
17021 
17022 
17023 EXCEPTION
17024   WHEN OTHERS THEN
17025     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
17026       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17027                                     debug_info);
17028     END IF;
17029 
17030     IF (SQLCODE < 0) then
17031       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
17032         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
17033                                       SQLERRM);
17034       END IF;
17035     END IF;
17036     RETURN(FALSE);
17037 
17038 END v_check_deferred_accounting;
17039 
17040 
17041 ------------------------------------------------------------------------------
17042 -- This function is used to validate distribution set information.
17043 --
17044 ------------------------------------------------------------------------------
17045 FUNCTION v_check_line_dist_set (
17046          p_invoice_rec                  IN
17047          AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
17048          p_invoice_lines_rec            IN OUT NOCOPY
17049          AP_IMPORT_INVOICES_PKG.r_line_info_rec,
17050          p_base_currency_code           IN            VARCHAR2,
17051          p_employee_id                  IN            NUMBER,
17052          p_gl_date_from_get_info        IN            DATE,
17053          p_set_of_books_id              IN            NUMBER,
17054          p_chart_of_accounts_id         IN            NUMBER,
17055          p_pa_installed                 IN            VARCHAR2,
17056          p_default_last_updated_by      IN            NUMBER,
17057          p_default_last_update_login    IN            NUMBER,
17058          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
17059          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
17060 IS
17061 
17062   dist_set_check_failure      EXCEPTION;
17063   current_calling_sequence    VARCHAR2(2000);
17064   debug_info                  VARCHAR2(500);
17065   l_current_invoice_status    VARCHAR2(1) := 'Y';
17066   l_dist_set_id
17067       NUMBER(15) := p_invoice_lines_rec.distribution_set_id;
17068   l_dist_set_id_per_name      NUMBER(15);
17069   l_inactive_date             DATE;
17070   l_inactive_date_per_name    DATE;
17071   l_total_percent_distribution
17072     AP_DISTRIBUTION_SETS.TOTAL_PERCENT_DISTRIBUTION%TYPE;
17073   l_dset_lines_tab            AP_IMPORT_VALIDATION_PKG.dset_line_tab_type;
17074   l_expd_item_date            ap_invoice_lines.expenditure_item_date%TYPE:= '';
17075   l_error_found               VARCHAR2(1);
17076   i                           BINARY_INTEGER := 0;
17077   l_running_total_amount      NUMBER := 0;
17078   l_running_total_base_amt    NUMBER := 0;
17079   l_max_amount                NUMBER := 0;
17080   l_max_i                     BINARY_INTEGER := 0;
17081   l_running_total_pa_qty      NUMBER := 0;
17082   l_max_pa_quantity           NUMBER := 0;
17083   l_max_i_pa_qty              BINARY_INTEGER := 0;
17084   l_first_pa_qty              BOOLEAN := TRUE;
17085   l_award_set_id              AP_DISTRIBUTION_SET_LINES.award_id%TYPE;
17086   l_award_id                  AP_DISTRIBUTION_SET_LINES.award_id%TYPE;
17087   l_msg_application           VARCHAR2(25);
17088   l_msg_type                  VARCHAR2(25);
17089   l_msg_token1                VARCHAR2(30);
17090   l_msg_token2                VARCHAR2(30);
17091   l_msg_token3                VARCHAR2(30);
17092   l_msg_count                 NUMBER;
17093   l_msg_data                  VARCHAR2(500);
17094   l_billable_flag             VARCHAR2(60) := '';
17095   l_overlayed_ccid            NUMBER;
17096   l_unbuilt_flex              VARCHAR2(240):='';
17097   l_reason_unbuilt_flex       VARCHAR2(2000):='';
17098 
17099 
17100   CURSOR dist_set_lines IS
17101   SELECT DSL.dist_code_combination_id,
17102          DSL.percent_distribution,
17103          DSL.type_1099,
17104          DSL.description,
17105          DSL.distribution_set_line_number,
17106          DSL.attribute_category,
17107          DSL.attribute1,
17108          DSL.attribute2,
17109          DSL.attribute3,
17110          DSL.attribute4,
17111          DSL.attribute5,
17112          DSL.attribute6,
17113          DSL.attribute7,
17114          DSL.attribute8,
17115          DSL.attribute9,
17116          DSL.attribute10,
17117          DSL.attribute11,
17118          DSL.attribute12,
17119          DSL.attribute13,
17120          DSL.attribute14,
17121          DSL.attribute15,
17122          'DIST_SET_LINE',
17123          DSL.project_accounting_context,
17124          DSL.project_id,
17125          DSL.task_id,
17126          DSL.expenditure_organization_id,
17127          DSL.expenditure_type,
17128          NULL, -- pa_quantity
17129          NULL, -- pa_addition_flag
17130          DSL.org_id,
17131          DSL.award_id,
17132          0,    -- amount
17133          0     -- base_amount
17134     FROM ap_distribution_set_lines DSL
17135    WHERE DSL.distribution_set_id = l_dist_set_id
17136    ORDER BY distribution_set_line_number;
17137 
17138    l_sys_link_function varchar2(2); ---bugfix:5725904
17139   BEGIN
17140     -- Update the calling sequence
17141     --
17142     current_calling_sequence :='AP_IMPORT_VALIDATION_PKG.v_check_line_dist_set'
17143                                || '<-' ||P_calling_sequence;
17144 
17145     ------------------------------------------------------------------------
17146     -- Step 1
17147     -- Validate Distribution Set Id
17148     ------------------------------------------------------------------------
17149     debug_info := '(Check Line Dist Set 1) Validate Distribution Set Id';
17150     ------------------------------------------------------------------------
17151     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17152       AP_IMPORT_UTILITIES_PKG.Print(
17153           AP_IMPORT_INVOICES_PKG.g_debug_switch,
17154           debug_info);
17155     END IF;
17156 
17157     BEGIN
17158       IF (p_invoice_lines_rec.distribution_set_id IS NOT NULL) THEN
17159         SELECT distribution_set_id , inactive_date, total_percent_distribution
17160           INTO l_dist_set_id, l_inactive_date, l_total_percent_distribution
17161           FROM ap_distribution_sets
17162          WHERE distribution_set_id = p_invoice_lines_rec.distribution_set_id;
17163       END IF;
17164 
17165       IF (p_invoice_lines_rec.distribution_set_name IS NOT NULL) THEN
17166         SELECT distribution_set_id , inactive_date, total_percent_distribution
17167           INTO l_dist_set_id_per_name, l_inactive_date_per_name,
17168            l_total_percent_distribution
17169           FROM ap_distribution_sets
17170          WHERE distribution_set_name
17171                = p_invoice_lines_rec.distribution_set_name;
17172       END IF;
17173 
17174     EXCEPTION
17175       WHEN no_data_found THEN
17176         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17177                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17178                 p_invoice_lines_rec.invoice_line_id,
17179                 'INVALID DISTRIBUTION SET',
17180                 p_default_last_updated_by,
17181                 p_default_last_update_login,
17182                 current_calling_sequence) <> TRUE) THEN
17183           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17184             AP_IMPORT_UTILITIES_PKG.Print(
17185                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
17186                 'insert_rejections<- '||current_calling_sequence);
17187           END IF;
17188           RAISE dist_set_check_failure;
17189         END IF;
17190 
17191         l_current_invoice_status := 'N';
17192         p_current_invoice_status := l_current_invoice_status;
17193       RETURN (TRUE);
17194     END;
17195 
17196 
17197     IF ((l_dist_set_id is NOT NULL) AND
17198         (l_dist_set_id_per_name is NOT NULL) AND
17199         (l_dist_set_id <> l_dist_set_id_per_name)) Then
17200       -----------------------------------------------------------------------
17201       -- Step 2
17202       -- Check for INCONSISTENT DIST SET
17203       -----------------------------------------------------------------------
17204       debug_info := '(Check Line Dist Set 2) Check for INCONSISTENT DIST SET';
17205       -----------------------------------------------------------------------
17206       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
17207         AP_IMPORT_UTILITIES_PKG.Print(
17208             AP_IMPORT_INVOICES_PKG.g_debug_switch,
17209             debug_info);
17210       End if;
17211 
17212       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17213               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17214               p_invoice_lines_rec.invoice_line_id,
17215               'INCONSISTENT DIST SET',
17216               p_default_last_updated_by,
17217               p_default_last_update_login,
17218               current_calling_sequence) <> TRUE) THEN
17219         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17220           AP_IMPORT_UTILITIES_PKG.Print(
17221               AP_IMPORT_INVOICES_PKG.g_debug_switch,
17222               'insert_rejections<-' ||current_calling_sequence);
17223         END IF;
17224         RAISE dist_set_check_failure;
17225       END IF;
17226 
17227       l_current_invoice_status := 'N';
17228 
17229     ELSE
17230       ----------------------------------------------------------------------
17231       -- Step 3
17232       -- look for inactive DIST SET
17233       ----------------------------------------------------------------------
17234       debug_info := '(Check Line Dist Set 3.1) Check for inactive DIST SET';
17235       ----------------------------------------------------------------------
17236       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17237         AP_IMPORT_UTILITIES_PKG.Print(
17238             AP_IMPORT_INVOICES_PKG.g_debug_switch,
17239             debug_info);
17240       END IF;
17241 
17242       IF (( AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
17243             nvl(trunc(l_inactive_date), AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))
17244             OR
17245            (AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
17246             nvl(trunc(l_inactive_date_per_name),
17247                 AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1))) THEN
17248 
17249         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17250                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17251                 p_invoice_lines_rec.invoice_line_id,
17252                 'INACTIVE DISTRIBUTION SET',
17253                 p_default_last_updated_by,
17254                 p_default_last_update_login,
17255                 current_calling_sequence) <> TRUE) THEN
17256           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17257             AP_IMPORT_UTILITIES_PKG.Print(
17258                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
17259                 'insert_rejections<- '||current_calling_sequence);
17260           END IF;
17261           RAISE dist_set_check_failure;
17262         END IF; -- end of insert_rejection
17263 
17264         l_current_invoice_status := 'N';
17265       END IF;  -- end of check l_active_date
17266       ----------------------------------------------------------------------
17267       debug_info := '(Check Line Dist Set 3.2) Use dist_set_id_per_name';
17268       ----------------------------------------------------------------------
17269       IF ((l_dist_set_id is Null) AND
17270           (l_dist_set_id_per_name is Not Null)) THEN
17271 
17272         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17273           AP_IMPORT_UTILITIES_PKG.Print(
17274               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17275         END IF;
17276         l_dist_set_id := l_dist_set_id_per_name;
17277       END IF;
17278     END IF; -- end of step 2 and step 3
17279 
17280     ----------------------------------------------------------------------
17281     -- Step 4
17282     -- Validate the info. in distribution set lines before proceeding
17283     -- further. At this point we have validated the basic distribution
17284     -- set information.  Now we need to validate project, task,
17285     -- expenditure details and award for each distribution set lines.
17286     -- Also we need to validate the account and overlayed accounts if any.
17287     ----------------------------------------------------------------------
17288     IF (l_dist_set_id is not null) THEN
17289       --------------------------------------------------------------------
17290       debug_info := '(v_check_line_dist_set 4.1) Get all ' ||
17291                     'the information in the distribution sets';
17292       --------------------------------------------------------------------
17293       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17294           AP_IMPORT_UTILITIES_PKG.Print(
17295               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17296       END IF;
17297       l_dset_lines_tab.DELETE;
17298       OPEN dist_set_lines;
17299       FETCH dist_set_lines BULK COLLECT INTO l_dset_lines_tab;
17300       CLOSE dist_set_lines;
17301 
17302 
17303       ------------------------------------------------------------------
17304       debug_info := '(v_check_line_dist_set 4.2) Loop through read '||
17305                 'dset lines and validate';
17306       ------------------------------------------------------------------
17307       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17308           AP_IMPORT_UTILITIES_PKG.Print(
17309         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17310       END IF;
17311 
17312       FOR i IN l_dset_lines_tab.first..l_dset_lines_tab.last
17313       LOOP
17314 
17315         ----------------------------------------------------------------
17316      debug_info := '(v_check_line_dist_set 4.2.a) Get expenditure '||
17317       'item date if null and dist set line will be project related';
17318     ----------------------------------------------------------------
17319         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17320           AP_IMPORT_UTILITIES_PKG.Print(
17321               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17322         END IF;
17323 
17324         IF (p_invoice_lines_rec.expenditure_item_date IS NULL AND
17325         l_expd_item_date IS NULL AND
17326         (p_invoice_lines_rec.project_id IS NOT NULL OR
17327          l_dset_lines_tab(i).project_id IS NOT NULL)) THEN
17328           l_expd_item_date := AP_INVOICES_PKG.get_expenditure_item_date(
17329                  p_invoice_rec.invoice_id,
17330                  p_invoice_rec.invoice_date,
17331                  nvl(p_invoice_lines_rec.accounting_date,
17332                      p_gl_date_from_get_info),
17333                  NULL,
17334                  NULL,
17335              l_error_found);
17336        IF (l_error_found = 'Y') then
17337              RAISE dist_set_check_failure;
17338            END IF;
17339         ELSIF (p_invoice_lines_rec.expenditure_item_date IS NOT NULL AND
17340            l_expd_item_date IS NULL) THEN
17341           l_expd_item_date := p_invoice_lines_rec.expenditure_item_date;
17342         END IF;
17343 
17344         -----------------------------------------------------------------
17345     debug_info := '(v_check_line_dist_set 4.2.b) Populate amount '||
17346       'and base amount for the distribution into PL/SQL table';
17347     -----------------------------------------------------------------
17348     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17349           AP_IMPORT_UTILITIES_PKG.Print(
17350               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17351         END IF;
17352         IF (l_total_percent_distribution <> 100) THEN
17353           l_dset_lines_tab(i).amount := 0;
17354       l_dset_lines_tab(i).base_amount := 0;
17355     ELSE
17356       l_dset_lines_tab(i).amount := AP_UTILITIES_PKG.Ap_Round_Currency(
17357                               NVL(l_dset_lines_tab(i).percent_distribution,0)
17358                      * NVL(p_invoice_lines_rec.amount,0)/100,
17359                   p_invoice_rec.invoice_currency_code);
17360           l_dset_lines_tab(i).base_amount :=
17361                           AP_UTILITIES_PKG.Ap_Round_Currency(
17362                  NVL(l_dset_lines_tab(i).amount, 0)
17363                  * NVL(p_invoice_rec.exchange_rate, 1),
17364                                  p_base_currency_code);
17365         END IF;
17366 
17367     --
17368     -- Maintain the running totals of the amounts for rounding
17369     l_running_total_amount := l_running_total_amount +
17370       l_dset_lines_tab(i).amount;
17371     l_running_total_base_amt := l_running_total_base_amt +
17372       l_dset_lines_tab(i).base_amount;
17373 
17374     -- Keep track of the particular distribution with the max
17375     -- amount.  That is the distribution that will take the
17376     -- rounding if any.
17377         IF (ABS(l_max_amount) <= ABS(l_dset_lines_tab(i).amount) OR
17378         i = 0) THEN
17379           l_max_amount := l_dset_lines_tab(i).amount;
17380       l_max_i := i;
17381     END IF;
17382 
17383     ----------------------------------------------------------------
17384     debug_info := '(v_check_line_dist_set 4.2.c) Populate project '||
17385       'info if either dist set line has it or invoice line has it';
17386     -------------------------------------------------------------------
17387     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17388           AP_IMPORT_UTILITIES_PKG.Print(
17389               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17390     END IF;
17391 
17392     -- If the distribution set line does not contain project
17393     -- information but the line does, then copy project information
17394     -- from the line.
17395     IF (l_dset_lines_tab(i).project_id IS NULL AND
17396          p_invoice_lines_rec.project_id IS NOT NULL) THEN
17397       l_dset_lines_tab(i).project_source := 'INVOICE_LINE';
17398       l_dset_lines_tab(i).project_accounting_context := 'Yes';
17399           l_dset_lines_tab(i).project_id := p_invoice_lines_rec.project_id;
17400       l_dset_lines_tab(i).task_id := p_invoice_lines_rec.task_id;
17401           l_dset_lines_tab(i).expenditure_type :=
17402         p_invoice_lines_rec.expenditure_type;
17403       l_dset_lines_tab(i).expenditure_organization_id :=
17404         p_invoice_lines_rec.expenditure_organization_id;
17405     END IF;
17406 
17407     -- Regardless of where the project information came from,
17408     -- track the pa quantity but only if this is not a skeleton
17409     -- distribution set and only if the distribution turns out to
17410     -- be project related.
17411     IF (l_dset_lines_tab(i).project_id IS NOT NULL) THEN
17412       IF (l_total_percent_distribution <> 100) THEN
17413         NULL;
17414       ELSE
17415         IF (p_invoice_lines_rec.pa_quantity IS NOT NULL AND
17416             p_invoice_lines_rec.amount <> 0) THEN
17417           l_dset_lines_tab(i).pa_quantity :=
17418       			     p_invoice_lines_rec.pa_quantity
17419                				* l_dset_lines_tab(i).amount /
17420                				p_invoice_lines_rec.amount;
17421         END IF;
17422       END IF;
17423 
17424       -- Keep track of the particular distribution with the max
17425       -- pa quantity.  That is the distribution that will take the
17426       -- rounding if any.
17427       IF (l_first_pa_qty AND
17428           l_dset_lines_tab(i).pa_quantity IS NOT NULL) THEN
17429             l_max_pa_quantity := l_dset_lines_tab(i).pa_quantity;
17430             l_max_i_pa_qty := i;
17431             l_first_pa_qty := FALSE;
17432       ELSIF (l_dset_lines_tab(i).pa_quantity IS NOT NULL AND
17433              NOT l_first_pa_qty ) THEN
17434         IF (ABS(l_max_pa_quantity) <=
17435             ABS(l_dset_lines_tab(i).pa_quantity)) THEN
17436           l_max_pa_quantity := l_dset_lines_tab(i).pa_quantity;
17437           l_max_i_pa_qty := i;
17438         END IF;
17439       END IF;
17440 
17441       l_running_total_pa_qty := Nvl(l_dset_lines_tab(i).pa_quantity,0);
17442       l_dset_lines_tab(i).pa_addition_flag := 'N';
17443 
17444     ELSE
17445       l_dset_lines_tab(i).pa_addition_flag := 'E';
17446 
17447     END IF; -- project id is not null
17448 
17449     -----------------------------------------------------------------
17450     debug_info := '(v_check_line_dist_set 4.2.d) Populate/validate '||
17451       'award information';
17452     -----------------------------------------------------------------
17453     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17454           AP_IMPORT_UTILITIES_PKG.Print(
17455               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17456         END IF;
17457     --
17458     -- Default award id from line if award id is not populated
17459     -- for the distribution set line.
17460     --
17461         IF ( l_current_invoice_status = 'Y') THEN
17462 
17463 	   IF (l_dset_lines_tab(i).award_id IS NOT NULL) THEN
17464 	       l_award_set_id := l_dset_lines_tab(i).award_id;
17465 	   ELSIF (p_invoice_lines_rec.award_id IS NOT NULL) THEN
17466 	      l_dset_lines_tab(i).award_id := p_invoice_lines_rec.award_id;
17467 	      l_award_id := p_invoice_lines_rec.award_id;
17468 	   END IF;
17469 
17470 	   IF (l_award_set_id IS NOT NULL) THEN
17471 	       GMS_AP_API.GET_DIST_SET_AWARD(
17472 		                l_dist_set_id,
17473 		                l_dset_lines_tab(i).distribution_set_line_number,
17474 		                l_award_set_id,
17475 		                l_award_id);
17476 
17477 	      l_dset_lines_tab(i).award_id:= l_award_id ;
17478 	  END IF;
17479 
17480 
17481           debug_info := '(v_check_line_dist_set 4.2.d.1) - ' ||
17482                         'Call GMS API to validate award info->temp award dist';
17483           IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17484             AP_IMPORT_UTILITIES_PKG.Print(
17485                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17486           END IF;
17487 
17488           ----------------------------------------------------------------
17489           debug_info := '(v_check_line_dist_set 4.2.d.1) - ' ||
17490                         'Get award id from award set from GMS' ;
17491           ----------------------------------------------------------------
17492           IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17493             AP_IMPORT_UTILITIES_PKG.Print(
17494                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17495           END IF;
17496           -- Get the value of award_id from GMS API
17497           -- Note that the award in the distribution set line or interface
17498           -- invoice line record is truly an award set id, we need GMS
17499           -- to derive the actual award id and the same must be stored in
17500           -- the distributions when they are created.
17501           -- The call is commented out because it does not exist in 11.6 yet.
17502           IF (l_award_set_id IS NOT NULL) THEN
17503              GMS_AP_API.GET_DIST_SET_AWARD(
17504                 l_dist_set_id,
17505                 l_dset_lines_tab(i).distribution_set_line_number,
17506                 l_award_set_id,
17507                 l_award_id);
17508           END IF;
17509 
17510           ---------------------------------------------------------------------
17511           debug_info := '(v_check_line_dist_set 4.2.d.2) - ' ||
17512                         'Call GMS API - validate award -l_award_id->' ||
17513                          to_char(l_award_id) ;
17514           ---------------------------------------------------------------------
17515           IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17516             AP_IMPORT_UTILITIES_PKG.Print(
17517                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17518           END IF;
17519 
17520           IF (GMS_AP_API.v_check_line_award_info (
17521               p_invoice_line_id  => p_invoice_lines_rec.invoice_line_id,
17522               p_line_amount      => l_dset_lines_tab(i).amount,
17523               p_base_line_amount => l_dset_lines_tab(i).base_amount,
17524               p_dist_code_concatenated   =>
17525             			          p_invoice_lines_rec.dist_code_concatenated,
17526               p_dist_code_combination_id =>
17527         			          l_dset_lines_tab(i).dist_code_combination_id,
17528               p_default_po_number        => NULL,
17529               p_po_number                => NULL,
17530               p_po_header_id             => NULL,
17531               p_distribution_set_id      => l_dist_set_id,
17532               p_distribution_set_name    =>
17533                 			p_invoice_lines_rec.distribution_set_name ,
17534               p_set_of_books_id          => p_set_of_books_id,
17535               p_base_currency_code       => p_base_currency_code,
17536               p_invoice_currency_code    =>
17537                 			p_invoice_rec.invoice_currency_code ,
17538               p_exchange_rate            => p_invoice_rec.exchange_rate,
17539               p_exchange_rate_type       =>
17540                 			p_invoice_rec.exchange_rate_type,
17541               p_exchange_rate_date       =>
17542                 			p_invoice_rec.exchange_date,
17543               p_project_id               => l_dset_lines_tab(i).project_id,
17544               p_task_id                  => l_dset_lines_tab(i).task_id,
17545               p_expenditure_type         =>
17546             				l_dset_lines_tab(i).expenditure_type,
17547               p_expenditure_item_date    => l_expd_item_date,
17548               p_expenditure_organization_id =>
17549                 			l_dset_lines_tab(i).expenditure_organization_id,
17550               p_project_accounting_context =>
17551             				l_dset_lines_tab(i).project_accounting_context,
17552               p_pa_addition_flag           =>
17553             				l_dset_lines_tab(i).pa_addition_flag,
17554               p_pa_quantity                =>
17555                 			l_dset_lines_tab(i).pa_quantity,
17556               p_employee_id                => p_employee_id,
17557               p_vendor_id                  => p_invoice_rec.vendor_id,
17558               p_chart_of_accounts_id       => p_chart_of_accounts_id,
17559               p_pa_installed               => p_pa_installed,
17560               p_prorate_across_flag        =>
17561                 			NVL(p_invoice_lines_rec.prorate_across_flag, 'N'),
17562               p_lines_attribute_category   =>
17563                 			p_invoice_lines_rec.attribute_category,
17564               p_lines_attribute1   => p_invoice_lines_rec.attribute1,
17565               p_lines_attribute2   => p_invoice_lines_rec.attribute2,
17566               p_lines_attribute3   => p_invoice_lines_rec.attribute3,
17567               p_lines_attribute4   => p_invoice_lines_rec.attribute4,
17568               p_lines_attribute5   => p_invoice_lines_rec.attribute5,
17569               p_lines_attribute6   => p_invoice_lines_rec.attribute6,
17570               p_lines_attribute7   => p_invoice_lines_rec.attribute7,
17571               p_lines_attribute8   => p_invoice_lines_rec.attribute8,
17572               p_lines_attribute9   => p_invoice_lines_rec.attribute9,
17573               p_lines_attribute10  => p_invoice_lines_rec.attribute10,
17574               p_lines_attribute11  => p_invoice_lines_rec.attribute11,
17575               p_lines_attribute12  => p_invoice_lines_rec.attribute12,
17576               p_lines_attribute13  => p_invoice_lines_rec.attribute13,
17577               p_lines_attribute14  => p_invoice_lines_rec.attribute14,
17578               p_lines_attribute15  => p_invoice_lines_rec.attribute15,
17579               p_attribute_category => l_dset_lines_tab(i).attribute_category,
17580               p_attribute1         => l_dset_lines_tab(i).attribute1,
17581               p_attribute2         => l_dset_lines_tab(i).attribute2,
17582               p_attribute3         => l_dset_lines_tab(i).attribute3,
17583               p_attribute4         => l_dset_lines_tab(i).attribute4,
17584               p_attribute5         => l_dset_lines_tab(i).attribute5,
17585               p_attribute6         => l_dset_lines_tab(i).attribute6,
17586               p_attribute7         => l_dset_lines_tab(i).attribute7,
17587               p_attribute8         => l_dset_lines_tab(i).attribute8,
17588               p_attribute9         => l_dset_lines_tab(i).attribute9,
17589               p_attribute10        => l_dset_lines_tab(i).attribute10,
17590               p_attribute11        => l_dset_lines_tab(i).attribute11,
17591               p_attribute12        => l_dset_lines_tab(i).attribute12,
17592               p_attribute13        => l_dset_lines_tab(i).attribute13,
17593               p_attribute14        => l_dset_lines_tab(i).attribute14,
17594               p_attribute15        => l_dset_lines_tab(i).attribute15,
17595               p_partial_segments_flag      =>
17596                                    p_invoice_lines_rec.partial_segments,
17597               p_default_last_updated_by    => p_default_last_updated_by,
17598               p_default_last_update_login  => p_default_last_update_login,
17599               p_calling_sequence   => current_calling_sequence ,
17600               p_award_id           => l_award_id,
17601               p_event              => 'AWARD_SET_ID_REQUEST' ) <> TRUE ) THEN
17602             --------------------------------------------------------------
17603             debug_info := '(v_check_line_dist_set 4.2.d.3) - ' ||
17604                           'After Call GMS API - Invalid GMS Info:Reject';
17605             --------------------------------------------------------------
17606             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17607               AP_IMPORT_UTILITIES_PKG.Print(
17608                  AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17609             END IF;
17610 
17611             IF ( AP_IMPORT_UTILITIES_PKG.insert_rejections(
17612                      AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17613                       p_invoice_lines_rec.invoice_line_id,
17614                       'INSUFFICIENT GMS INFO',
17615                       p_default_last_updated_by,
17616                       p_default_last_update_login,
17617                       current_calling_sequence) <> TRUE) THEN
17618               RAISE dist_set_check_failure;
17619             END IF;
17620             l_current_invoice_status := 'N';
17621           END IF; -- End of gms_ap_api.v_check_line_award_info.
17622         END IF; -- end of check l_current_invoice_status
17623 
17624         -----------------------------------------------------------
17625         debug_info := '(v_check_line_dist_set 4.2.e) - ' ||
17626                   'Validate project information';
17627         -----------------------------------------------------------
17628         IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17629           AP_IMPORT_UTILITIES_PKG.Print(
17630              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17631         END IF;
17632         IF (l_dset_lines_tab(i).project_id is not null AND
17633         l_current_invoice_status = 'Y') THEN
17634 
17635 	  --bugfxi:5725904
17636 	  If (p_invoice_rec.invoice_type_lookup_code ='EXPENSE REPORT') Then
17637 	        l_sys_link_function :='ER' ;
17638 	  Else
17639 	        l_sys_link_function :='VI' ;
17640 	  End if;
17641 
17642           PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION(
17643             X_PROJECT_ID          => l_dset_lines_tab(i).project_id,
17644             X_TASK_ID             => l_dset_lines_tab(i).task_id,
17645             X_EI_DATE             => l_expd_item_date,
17646             X_EXPENDITURE_TYPE    => l_dset_lines_tab(i).expenditure_type,
17647             X_NON_LABOR_RESOURCE  => null,
17648             X_PERSON_ID           => p_employee_id,
17649             X_QUANTITY            => NVL(l_dset_lines_tab(i).pa_quantity,'1'),
17650             X_denom_currency_code => p_invoice_rec.invoice_currency_code,
17651             X_acct_currency_code  => p_base_currency_code,
17652             X_denom_raw_cost      => l_dset_lines_tab(i).amount,
17653             X_acct_raw_cost       => l_dset_lines_tab(i).base_amount,
17654             X_acct_rate_type      => p_invoice_rec.exchange_rate_type,
17655             X_acct_rate_date      => p_invoice_rec.exchange_date,
17656             X_acct_exchange_rate  => p_invoice_rec.exchange_rate,
17657             X_TRANSFER_EI         => null,
17658             X_INCURRED_BY_ORG_ID  =>
17659           	l_dset_lines_tab(i).expenditure_organization_id,
17660             X_NL_RESOURCE_ORG_ID  => null,
17661             X_TRANSACTION_SOURCE  => l_sys_link_function,--Bug 3487412 --bug:5725904
17662             X_CALLING_MODULE      => 'apiimptb.pls',
17663             X_VENDOR_ID           => p_invoice_rec.vendor_id,
17664             X_ENTERED_BY_USER_ID  => to_number(FND_GLOBAL.USER_ID),
17665             X_ATTRIBUTE_CATEGORY  => l_dset_lines_tab(i).attribute_category,
17666             X_ATTRIBUTE1          => l_dset_lines_tab(i).attribute1,
17667             X_ATTRIBUTE2          => l_dset_lines_tab(i).attribute2,
17668             X_ATTRIBUTE3          => l_dset_lines_tab(i).attribute3,
17669             X_ATTRIBUTE4          => l_dset_lines_tab(i).attribute4,
17670             X_ATTRIBUTE5          => l_dset_lines_tab(i).attribute5,
17671             X_ATTRIBUTE6          => l_dset_lines_tab(i).attribute6,
17672             X_ATTRIBUTE7          => l_dset_lines_tab(i).attribute7,
17673             X_ATTRIBUTE8          => l_dset_lines_tab(i).attribute8,
17674             X_ATTRIBUTE9          => l_dset_lines_tab(i).attribute9,
17675             X_ATTRIBUTE10         => l_dset_lines_tab(i).attribute10,
17676             X_ATTRIBUTE11         => l_dset_lines_tab(i).attribute11,
17677             X_ATTRIBUTE12         => l_dset_lines_tab(i).attribute12,
17678             X_ATTRIBUTE13         => l_dset_lines_tab(i).attribute13,
17679             X_ATTRIBUTE14         => l_dset_lines_tab(i).attribute14,
17680             X_ATTRIBUTE15         => l_dset_lines_tab(i).attribute15,
17681             X_msg_application     => l_msg_application,
17682             X_msg_type            => l_msg_type,
17683             X_msg_token1          => l_msg_token1,
17684             X_msg_token2          => l_msg_token2,
17685             X_msg_token3          => l_msg_token3,
17686             X_msg_count           => l_msg_count,
17687             X_msg_data            => l_msg_data,
17688             X_BILLABLE_FLAG       => l_billable_flag,
17689             P_Document_Type       => p_invoice_rec.invoice_type_lookup_code,
17690             P_Document_Line_Type  => p_invoice_lines_rec.line_type_lookup_code);
17691 
17692           IF (l_msg_data IS NOT NULL) THEN
17693             --------------------------------------------------------------
17694          debug_info := '(v_check_line_dist_set 4.2.e.1) - Project '
17695                       ||'validate '
17696                           ||'PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION Fails'
17697                           ||'->Insert Rejection';
17698             --------------------------------------------------------------
17699             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17700               AP_IMPORT_UTILITIES_PKG.Print(
17701                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17702             END IF;
17703 
17704              -- Bug 5214592 . Added the debug message.
17705              debug_info := SUBSTR(l_msg_data,1,80);
17706              IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17707               AP_IMPORT_UTILITIES_PKG.Print(
17708                   AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17709               END IF;
17710 
17711 
17712             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17713                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17714                       p_invoice_lines_rec.invoice_line_id,
17715                       'PA FLEXBUILD FAILED',
17716                       p_default_last_updated_by,
17717                       p_default_last_update_login,
17718                       current_calling_sequence) <> TRUE) THEN
17719               RAISE dist_set_check_failure;
17720             END IF;
17721 
17722             l_current_invoice_status := 'N';
17723 
17724           END IF; -- end of check l_msg_data is not null
17725         END IF;-- end of l_project_id not null/l_current_invoice_status = 'Y'
17726 
17727         -----------------------------------------------------------------
17728         -- Validate account and account overlay depending on set of
17729     -- available data
17730         --
17731         debug_info := '(v_check_line_dist_set 4.2.f) - ' ||
17732                       'validate account';
17733         -----------------------------------------------------------------
17734         IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17735           AP_IMPORT_UTILITIES_PKG.Print(
17736               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17737         END IF;
17738 
17739         IF ((l_dset_lines_tab(i).project_id IS NULL AND
17740          p_invoice_lines_rec.dist_code_combination_id IS NULL) OR
17741         (l_dset_lines_tab(i).project_id IS NOT NULL AND
17742          l_dset_lines_tab(i).project_source <> 'INVOICE_LINE')) THEN
17743       --
17744           -- Account source is not at the line. Overlay may happen.
17745           -- We need to avoid redoing the account validations done
17746       -- at the line.  If there is no default account (dist_code
17747       -- combination_id at the line is null) and either there is
17748       -- no project info in this distribution or the project info
17749       -- does not come from the line, then new account sources
17750       -- are considered and we do need to validate.
17751       --
17752           IF (p_invoice_lines_rec.dist_code_combination_id IS NULL AND
17753               p_invoice_lines_rec.dist_code_concatenated is NULL AND
17754               p_invoice_lines_rec.balancing_segment is NULL AND
17755               p_invoice_lines_rec.account_segment is NULL AND
17756               p_invoice_lines_rec.cost_center_segment is NULL) THEN
17757 
17758             -------------------------------------------------------------
17759         	debug_info := '(v_check_line_dist_set 4.2.f.1) - ' ||
17760                   'validate account from dist set line - no overlay';
17761             -------------------------------------------------------------
17762             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17763               AP_IMPORT_UTILITIES_PKG.Print(
17764                 AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17765             END IF;
17766 
17767             IF ( NOT (AP_UTILITIES_PKG.IS_CCID_VALID(
17768                         l_dset_lines_tab(i).dist_code_combination_id,
17769                 	p_chart_of_accounts_id,
17770             		nvl(p_invoice_lines_rec.accounting_date,
17771                         p_gl_date_from_get_info),
17772                   	current_calling_sequence))) THEN
17773               IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17774                     AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17775                     p_invoice_lines_rec.invoice_line_id,
17776                     'INVALID DISTRIBUTION ACCT',
17777                     p_default_last_updated_by,
17778                     p_default_last_update_login,
17779                     current_calling_sequence) <> TRUE) THEN
17780                 RAISE dist_set_check_failure;
17781               END IF;
17782 
17783               l_current_invoice_status := 'N';
17784 
17785             END IF; -- end of call function IS_CCID_VALID
17786 
17787           --
17788       -- Again don't overlay and validate if the concatenated segments
17789       -- is other than partial, since that has already been done at
17790       -- line level and that would completely override the dist set line
17791           -- account so, no new validation would be performed.
17792       --
17793           ELSIF (p_invoice_lines_rec.dist_code_combination_id IS NULL AND
17794          (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL OR
17795           p_invoice_lines_rec.balancing_segment is NOT NULL OR
17796                   p_invoice_lines_rec.account_segment is NOT NULL OR
17797                   p_invoice_lines_rec.cost_center_segment is NOT NULL)) THEN
17798         --
17799             -- Make sure we don't go through the overlay and validation
17800             -- if the concatenated segments was full or if the line is
17801         -- project related and projects does not allow override
17802         --
17803             IF ((p_invoice_lines_rec.dist_code_concatenated IS NULL OR
17804          (p_invoice_lines_rec.dist_code_concatenated IS NOT NULL AND
17805           p_invoice_lines_rec.partial_segments <> 'N')) AND
17806         (l_dset_lines_tab(i).project_id IS NULL OR
17807          AP_IMPORT_INVOICES_PKG.g_pa_allows_overrides = 'Y')) THEN
17808           l_overlayed_ccid := l_dset_lines_tab(i).dist_code_combination_id;
17809 
17810           -----------------------------------------------------------
17811           debug_info := '(v_check_line_dist_set 4.2.f.2) - ' ||
17812                  'overlay dist set line account with line overlay data';
17813               -----------------------------------------------------------
17814               IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17815                   AP_IMPORT_UTILITIES_PKG.Print(
17816                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17817               END IF;
17818               IF ( NOT (AP_UTILITIES_PKG.OVERLAY_SEGMENTS (
17819                           p_invoice_lines_rec.balancing_segment,
17820                           p_invoice_lines_rec.cost_center_segment,
17821                           p_invoice_lines_rec.account_segment,
17822                           p_invoice_lines_rec.dist_code_concatenated,
17823                           l_overlayed_ccid,
17824                           p_set_of_books_id,
17825                           'CREATE_COMB_NO_AT',
17826                           l_unbuilt_flex,
17827                           l_reason_unbuilt_flex,
17828                           FND_GLOBAL.RESP_APPL_ID,
17829                           FND_GLOBAL.RESP_ID,
17830                           FND_GLOBAL.USER_ID,
17831                           current_calling_sequence))) THEN
17832         --------------------------------------------------------
17833         debug_info := 'Failure found during overlay';
17834         debug_info := debug_info || '-> l_unbuilt_flex= ' ||
17835                             l_unbuilt_flex ||
17836                             '-> l_dist_ccid=' ||
17837                             to_char(l_overlayed_ccid);
17838                 --------------------------------------------------------
17839                 IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17840                   AP_IMPORT_UTILITIES_PKG.Print(
17841                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17842                 END IF;
17843                 RAISE dist_set_check_failure;
17844           ELSE
17845             IF (l_overlayed_ccid = -1) THEN
17846               ----------------------------------------------------------
17847               -- debug_info := 'Overlay return -1';
17848           ----------------------------------------------------------
17849                   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17850             AP_IMPORT_UTILITIES_PKG.Print(
17851                       AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17852                   END IF;
17853 
17854                   IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
17855                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17856                        p_invoice_lines_rec.invoice_line_id,
17857                       'INVALID ACCT OVERLAY',
17858                        p_default_last_updated_by,
17859                        p_default_last_update_login,
17860                        current_calling_sequence) <> TRUE) THEN
17861                     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17862           		    AP_IMPORT_UTILITIES_PKG.Print(
17863              			AP_IMPORT_INVOICES_PKG.g_debug_switch,
17864                          	  'insert_rejections<-'||current_calling_sequence);
17865                     END IF;
17866                     RAISE dist_set_check_failure;
17867 
17868                   END IF;
17869 
17870                   l_current_invoice_status := 'N';
17871 
17872                 END IF; -- Code combination id is -1
17873 
17874               END IF; -- Overlay returned other than TRUE
17875 
17876             END IF; -- Overlay info is available, and we should try overlay
17877 
17878           END IF; -- Overaly info is available
17879 
17880         END IF; -- The distribution may require overlay or at least validation
17881                -- of the account since the account won't come from the line
17882             -- which has already validated its account/overlay.
17883 
17884         -------------------------------------------------------------------
17885         -- Call Grants - Clean up
17886         --
17887         debug_info := '(v_check_line_dist_set 4.2.g) - ' ||
17888                       'AWARD_ID_REMOVE: Check  GMS Info ';
17889         -------------------------------------------------------------------
17890         IF (l_current_invoice_status = 'Y' AND l_award_id is not null) THEN
17891           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
17892             AP_IMPORT_UTILITIES_PKG.Print(
17893               AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17894           END IF;
17895 
17896 	  GMS_AP_API.validate_transaction
17897               ( x_project_id		=> l_dset_lines_tab(i).project_id,
17898 		x_task_id		=> l_dset_lines_tab(i).task_id,
17899 		x_award_id		=> l_award_id,
17900 		x_expenditure_type	=> l_dset_lines_tab(i).expenditure_type,
17901 		x_expenditure_item_date => l_expd_item_date,
17902 		x_calling_sequence      => 'AWARD_ID',
17903 		x_msg_application       => l_msg_application,
17904 		x_msg_type              => l_msg_type,
17905 		x_msg_count             => l_msg_count,
17906 		x_msg_data              => l_msg_data ) ;
17907 
17908 	  IF (l_msg_data IS NOT NULL) THEN
17909 	      --------------------------------------------------------------
17910 	      debug_info := '(v_check_line_dist_set 4.2.d.3) - ' ||
17911 				'After Call GMS API - Invalid GMS Info:Reject';
17912 	      --------------------------------------------------------------
17913 	      IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
17914 	           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
17915 	      END IF;
17916 
17917 	      IF ( AP_IMPORT_UTILITIES_PKG.insert_rejections(
17918 	      	      	      AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
17919 	      	      	      p_invoice_lines_rec.invoice_line_id,
17920 	      	      	      'INSUFFICIENT GMS INFO',
17921 	      	      	      p_default_last_updated_by,
17922 	      	      	      p_default_last_update_login,
17923 	      	      	      current_calling_sequence) <> TRUE) THEN
17924 
17925 	      	      RAISE dist_set_check_failure;
17926 	      END IF;
17927 	      l_current_invoice_status := 'N';
17928 	  END IF;
17929 
17930         END IF; -- l_current_invoice_Status ='Y' AND l_award_id is not null
17931 
17932       END LOOP;
17933 
17934       -----------------------------------------------------------------------
17935       -- Step 5 - Re-Validate PA info if it is not a skeleton distribution set
17936       -- and there was rounding in the amount
17937       -----------------------------------------------------------------------
17938 
17939       IF ( l_current_invoice_status = 'Y'  AND
17940            l_total_percent_distribution = 100 AND
17941        (p_invoice_lines_rec.amount <> l_running_total_amount OR
17942         p_invoice_lines_rec.base_amount <> l_running_total_base_amt OR
17943         Nvl(p_invoice_lines_rec.pa_quantity, 0) <>
17944         Nvl(l_running_total_pa_qty,0))) THEN
17945 
17946     --
17947     -- If rounding in the amount for a project related distribution
17948     -- then lump all rounding onto the same distribution.
17949     -- Else, find the distribution for any pa quantity rounding.
17950     --
17951     IF (l_dset_lines_tab(l_max_i).project_id IS NOT NULL) THEN
17952 
17953           l_dset_lines_tab(l_max_i).amount := l_dset_lines_tab(l_max_i).amount
17954         + p_invoice_lines_rec.amount
17955         - l_running_total_amount;
17956       l_dset_lines_tab(l_max_i).base_amount :=
17957         l_dset_lines_tab(l_max_i).base_amount
17958         + p_invoice_lines_rec.base_amount
17959         - l_running_total_base_amt;
17960       IF (l_dset_lines_tab(l_max_i).pa_quantity IS NOT NULL) THEN
17961           l_dset_lines_tab(l_max_i).pa_quantity :=
17962           l_dset_lines_tab(l_max_i).pa_quantity
17963           + p_invoice_lines_rec.pa_quantity
17964           - l_running_total_pa_qty;
17965       END IF;
17966 
17967     ELSIF l_dset_lines_tab.exists(l_max_i_pa_qty) THEN  -- Bug 5713771
17968       IF   (l_dset_lines_tab(l_max_i_pa_qty).project_id IS NOT NULL AND
17969            l_dset_lines_tab(l_max_i_pa_qty).pa_quantity IS NOT NULL) THEN
17970 
17971         l_dset_lines_tab(l_max_i_pa_qty).pa_quantity :=
17972         l_dset_lines_tab(l_max_i_pa_qty).pa_quantity
17973         + p_invoice_lines_rec.pa_quantity
17974         - l_running_total_pa_qty;
17975         l_max_i := l_max_i_pa_qty;
17976       END IF;
17977     END IF;
17978 
17979     IF (l_dset_lines_tab(l_max_i).project_id IS NOT NULL) THEN
17980 
17981           If (p_invoice_rec.invoice_type_lookup_code ='EXPENSE REPORT') Then
17982               l_sys_link_function :='ER' ;
17983           Else
17984 	      l_sys_link_function :='VI' ;
17985 	  End if;
17986 
17987           PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION(
17988           X_PROJECT_ID          => l_dset_lines_tab(l_max_i).project_id,
17989           X_TASK_ID             => l_dset_lines_tab(l_max_i).task_id,
17990           X_EI_DATE             => l_expd_item_date,
17991           X_EXPENDITURE_TYPE    => l_dset_lines_tab(l_max_i).expenditure_type,
17992           X_NON_LABOR_RESOURCE  => null,
17993           X_PERSON_ID           => p_employee_id,
17994           X_QUANTITY            => Nvl(l_dset_lines_tab(l_max_i).pa_quantity,
17995                                        '1'),
17996           X_denom_currency_code => p_invoice_rec.invoice_currency_code,
17997           X_acct_currency_code  => p_base_currency_code,
17998           X_denom_raw_cost      => l_dset_lines_tab(l_max_i).amount,
17999           X_acct_raw_cost       => l_dset_lines_tab(l_max_i).base_amount,
18000           X_acct_rate_type      => p_invoice_rec.exchange_rate_type,
18001           X_acct_rate_date      => p_invoice_rec.exchange_date,
18002           X_acct_exchange_rate  => p_invoice_rec.exchange_rate,
18003           X_TRANSFER_EI         => null,
18004           X_INCURRED_BY_ORG_ID  =>
18005              l_dset_lines_tab(l_max_i).expenditure_organization_id,
18006           X_NL_RESOURCE_ORG_ID  => null,
18007           X_TRANSACTION_SOURCE  => l_sys_link_function,--Bug 3487412 made the change
18008           X_CALLING_MODULE      => 'apiimptb.pls',
18009           X_VENDOR_ID           => p_invoice_rec.vendor_id,
18010           X_ENTERED_BY_USER_ID  => to_number(FND_GLOBAL.USER_ID),
18011           X_ATTRIBUTE_CATEGORY  =>
18012               l_dset_lines_tab(l_max_i).attribute_category,
18013           X_ATTRIBUTE1          => l_dset_lines_tab(l_max_i).attribute1,
18014           X_ATTRIBUTE2          => l_dset_lines_tab(l_max_i).attribute2,
18015           X_ATTRIBUTE3          => l_dset_lines_tab(l_max_i).attribute3,
18016           X_ATTRIBUTE4          => l_dset_lines_tab(l_max_i).attribute4,
18017           X_ATTRIBUTE5          => l_dset_lines_tab(l_max_i).attribute5,
18018           X_ATTRIBUTE6          => l_dset_lines_tab(l_max_i).attribute6,
18019           X_ATTRIBUTE7          => l_dset_lines_tab(l_max_i).attribute7,
18020           X_ATTRIBUTE8          => l_dset_lines_tab(l_max_i).attribute8,
18021           X_ATTRIBUTE9          => l_dset_lines_tab(l_max_i).attribute9,
18022           X_ATTRIBUTE10         => l_dset_lines_tab(l_max_i).attribute10,
18023           X_ATTRIBUTE11         => l_dset_lines_tab(l_max_i).attribute11,
18024           X_ATTRIBUTE12         => l_dset_lines_tab(l_max_i).attribute12,
18025           X_ATTRIBUTE13         => l_dset_lines_tab(l_max_i).attribute13,
18026           X_ATTRIBUTE14         => l_dset_lines_tab(l_max_i).attribute14,
18027           X_ATTRIBUTE15         => l_dset_lines_tab(l_max_i).attribute15,
18028           X_msg_application     => l_msg_application,
18029           X_msg_type            => l_msg_type,
18030           X_msg_token1          => l_msg_token1,
18031           X_msg_token2          => l_msg_token2,
18032           X_msg_token3          => l_msg_token3,
18033           X_msg_count           => l_msg_count,
18034           X_msg_data            => l_msg_data,
18035           X_BILLABLE_FLAG       => l_billable_flag,
18036           P_Document_Type       => p_invoice_rec.invoice_type_lookup_code,
18037           P_Document_Line_Type  => p_invoice_lines_rec.line_type_lookup_code);
18038           IF (l_msg_data IS NOT NULL) THEN
18039             -----------------------------------------------------------------
18040             debug_info := '(v_check_line_dist_set 5.1) - Project validate '
18041                             || 'PA_TRANSACTIONS_PUB.VALIDATE_TRANSACTION Fails'
18042                             || 'for rounding ->Insert Rejection';
18043             -----------------------------------------------------------------
18044             IF ( AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y' ) THEN
18045               AP_IMPORT_UTILITIES_PKG.Print(
18046                     AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18047             END IF;
18048 
18049             IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18050                       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18051                       p_invoice_lines_rec.invoice_line_id,
18052                       'PA FLEXBUILD FAILED',
18053                       p_default_last_updated_by,
18054                       p_default_last_update_login,
18055                       current_calling_sequence) <> TRUE) THEN
18056               RAISE dist_set_check_failure;
18057             END IF;
18058 
18059             l_current_invoice_status := 'N';
18060 
18061           END IF; -- end of check l_msg_data is not null
18062         END IF; -- end of check l_project_id is not null
18063 
18064       END IF;  -- rounding existed
18065 
18066       l_dset_lines_tab.DELETE;
18067 
18068     END IF; -- end of l_dist_set_id is not null
18069 
18070 
18071     IF  (l_current_invoice_status <> 'N') THEN
18072       IF (l_dist_set_id is not NULL) THEN
18073         p_invoice_lines_rec.distribution_set_id := l_dist_set_id;
18074       END IF;
18075     END IF;
18076 
18077     p_current_invoice_status := l_current_invoice_status;
18078     RETURN (TRUE);
18079 
18080   EXCEPTION
18081     WHEN OTHERS THEN
18082       -- Clean up
18083       IF ( Dist_Set_Lines%ISOPEN ) THEN
18084         CLOSE Dist_Set_Lines;
18085       END IF;
18086       l_dset_lines_tab.DELETE;
18087 
18088       debug_info := '(v_check_line_dist_set ) -> ' ||
18089       'exception occurs ->' ;
18090       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18091         AP_IMPORT_UTILITIES_PKG.Print(
18092             AP_IMPORT_INVOICES_PKG.g_debug_switch,
18093             debug_info);
18094       END IF;
18095 
18096       IF (SQLCODE < 0) THEN
18097         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18098             AP_IMPORT_UTILITIES_PKG.Print(
18099                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18100                 SQLERRM);
18101         END IF;
18102       END IF;
18103       RETURN(FALSE);
18104 END v_check_line_dist_set;
18105 
18106 ------------------------------------------------------------------------------
18107 -- This function is used to validate qty/UOM information for non PO/RCV
18108 -- matched lines
18109 --
18110 ------------------------------------------------------------------------------
18111 FUNCTION v_check_qty_uom_non_po (
18112          p_invoice_rec  IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
18113          p_invoice_lines_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18114          p_default_last_updated_by      IN            NUMBER,
18115          p_default_last_update_login    IN            NUMBER,
18116          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
18117          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
18118 
18119 IS
18120 
18121 qty_uom_check_failure            EXCEPTION;
18122 l_uom_is_valid                       VARCHAR2(30);
18123 l_current_invoice_status         VARCHAR2(1) := 'Y';
18124 current_calling_sequence          VARCHAR2(2000);
18125 debug_info                       VARCHAR2(500);
18126 
18127 BEGIN
18128   -- Update the calling sequence
18129   --
18130   current_calling_sequence :=
18131     'AP_IMPORT_VALIDATION_PKG.v_check_qty_uom_non_po <-'||P_calling_sequence;
18132 
18133   IF (p_invoice_lines_rec.po_header_id is NOT NULL OR
18134       p_invoice_lines_rec.rcv_transaction_id is NOT NULL) THEN
18135     --------------------------------------------------------------------------
18136     -- Step 1
18137     -- Nothing to do since this is PO/RCV matched
18138     --------------------------------------------------------------------------
18139     debug_info := '(Check Qty UOM non PO 1) Nothing to do.';
18140     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18141       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18142                                     debug_info);
18143     END IF;
18144 
18145     p_current_invoice_status := l_current_invoice_status;
18146     RETURN (TRUE);
18147 
18148   ELSE
18149     -------------------------------------------------------------------------
18150     -- Step 2
18151     -- Check that if quantity related information was provided the line type
18152     -- is Item
18153     -------------------------------------------------------------------------
18154     debug_info :=
18155       '(Check Qty UOM non PO 2) Check Qty related information vs line type.';
18156     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18157       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18158                                     debug_info);
18159     END IF;
18160 
18161     IF (p_invoice_lines_rec.line_type_lookup_code NOT IN ( 'ITEM', 'RETROITEM') AND
18162         (p_invoice_lines_rec.quantity_invoiced IS NOT NULL OR
18163          p_invoice_lines_rec.unit_of_meas_lookup_code IS NOT NULL OR
18164          p_invoice_lines_rec.unit_price IS NOT NULL)) THEN
18165       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18166          AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18167           p_invoice_lines_rec.invoice_line_id,
18168          'INVALID QTY INFO',
18169           p_default_last_updated_by,
18170           p_default_last_update_login,
18171           current_calling_sequence) <> TRUE) THEN
18172         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18173           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18174             'insert_rejections<-'||current_calling_sequence);
18175         END IF;
18176         RAISE qty_uom_check_failure;
18177       END IF;
18178 
18179       l_current_invoice_status := 'N';
18180 
18181     END IF;
18182     /* Bug 5763126 Checking in step 3 is not required
18183      --The validation is already done in step 2
18184     --------------------------------------------------------------------------
18185     -- Step 3
18186     -- Check that if quantity related information  was provided so was the UOM.
18187     --  Only do this check for Item lines.
18188     -------------------------------------------------------------------------
18189     debug_info := '(Check Qty UOM non PO 3) Check Qty information vs UOM';
18190     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18191       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18192                                     debug_info);
18193     END IF;
18194 
18195     IF (p_invoice_lines_rec.line_type_lookup_code  IN ('ITEM', 'RETROITEM') AND
18196         (p_invoice_lines_rec.quantity_invoiced IS NOT NULL OR
18197          p_invoice_lines_rec.unit_price IS NOT NULL) AND
18198         p_invoice_lines_rec.unit_of_meas_lookup_code is NULL) THEN
18199 
18200       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18201            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18202            p_invoice_lines_rec.invoice_line_id,
18203           'INCOMPLETE QTY INFO',
18204             p_default_last_updated_by,
18205             p_default_last_update_login,
18206             current_calling_sequence) <> TRUE) THEN
18207         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18208           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18209             'insert_rejections<-'||current_calling_sequence);
18210         END IF;
18211         RAISE qty_uom_check_failure;
18212       END IF;
18213 
18214       l_current_invoice_status := 'N';
18215 
18216     END IF;
18217        */   -- Bug 5763126 End
18218     -------------------------------------------------------------------------
18219     -- Step 4
18220     -- Check that if UOM is provided, then either quantity invoiced is
18221     -- provided or can be derived from amount and unit price.  Only do this
18222     -- check for Item lines. Also derive unit price if possible and verify
18223     -- consistency of unit price, qty and amount for the line.
18224     -------------------------------------------------------------------------
18225     debug_info := '(Check Qty UOM non PO 4) Check Qty information when UOM '
18226                   ||'populated';
18227     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18228       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18229                                    debug_info);
18230     END IF;
18231 
18232     IF (p_invoice_lines_rec.line_type_lookup_code IN  ('ITEM', 'RETROITEM') AND
18233         p_invoice_lines_rec.unit_of_meas_lookup_code IS NOT NULL) THEN
18234       -----------------------------------------------------------------------
18235       -- Step 4a
18236       -- If quantity invoiced is null and unit price and line amount are not,
18237       -- derive the quantity invoiced.
18238       -----------------------------------------------------------------------
18239       IF (p_invoice_lines_rec.quantity_invoiced is NULL) THEN
18240         debug_info := '(Check Qty UOM non PO 4a) Qty invoiced is null.  Try '
18241                        ||'to derive it';
18242         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18243           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18244                                         debug_info);
18245         END IF;
18246 
18247         IF (p_invoice_lines_rec.amount IS NOT NULL AND
18248             p_invoice_lines_rec.unit_price IS NOT NULL) THEN
18249          IF (p_invoice_lines_rec.unit_price = 0) THEN
18250             p_invoice_lines_rec.quantity_invoiced :=
18251               p_invoice_lines_rec.amount;
18252           ELSE
18253             p_invoice_lines_rec.quantity_invoiced :=
18254               p_invoice_lines_rec.amount / p_invoice_lines_rec.unit_price;
18255           END IF;
18256 
18257         ELSE -- We dont have enough data to get quantity invoiced
18258           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18259               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18260               p_invoice_lines_rec.invoice_line_id,
18261              'INCOMPLETE QTY INFO',
18262               p_default_last_updated_by,
18263               p_default_last_update_login,
18264               current_calling_sequence) <> TRUE) THEN
18265             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18266               AP_IMPORT_UTILITIES_PKG.Print(
18267                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18268                'insert_rejections<-'||current_calling_sequence);
18269             END IF;
18270             RAISE qty_uom_check_failure;
18271           END IF;
18272           l_current_invoice_status := 'N';
18273         END IF; -- amount and unit price are not null
18274       END IF; -- quantity invoiced is null
18275 
18276       -----------------------------------------------------------------------
18277       -- Step 4b
18278       -- If quantity invoiced provided, verify that it is non 0
18279       --
18280       -----------------------------------------------------------------------
18281       IF (p_invoice_lines_rec.quantity_invoiced is NOT NULL AND
18282           p_invoice_lines_rec.quantity_invoiced = 0) THEN
18283         debug_info := '(Check Qty UOM non PO 4b) Verify qty invoice is non 0';
18284         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18285           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18286                                         debug_info);
18287         END IF;
18288 
18289         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18290             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18291             p_invoice_lines_rec.invoice_line_id,
18292             'INVALID QTY INFO',
18293              p_default_last_updated_by,
18294              p_default_last_update_login,
18295              current_calling_sequence) <> TRUE) THEN
18296           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18297             AP_IMPORT_UTILITIES_PKG.Print(
18298                  AP_IMPORT_INVOICES_PKG.g_debug_switch,
18299             'insert_rejections<-'||current_calling_sequence);
18300           END IF;
18301           RAISE qty_uom_check_failure;
18302         END IF;
18303       END IF;
18304 
18305       ------------------------------------------------------------------------
18306       -- Step 4c
18307       -- If quantity invoiced and line amount are not null but unit price is
18308       -- null, derive unit price.
18309       ------------------------------------------------------------------------
18310       IF (p_invoice_lines_rec.quantity_invoiced is NOT NULL AND
18311           p_invoice_lines_rec.amount is NOT NULL AND
18312           p_invoice_lines_rec.unit_price is NULL) THEN
18313         debug_info :=
18314           '(Check Qty UOM non PO 4c) Unit price is null.  Try to derive it';
18315         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18316           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18317             debug_info);
18318         END IF;
18319         IF (p_invoice_lines_rec.quantity_invoiced <> 0) THEN
18320           p_invoice_lines_rec.unit_price := p_invoice_lines_rec.amount/
18321                                  p_invoice_lines_rec.quantity_invoiced;
18322         END IF;
18323       END IF;
18324 
18325       -----------------------------------------------------------------------
18326       -- Step 4d
18327       -- If quantity invoiced, unit_price and line amount are populated,
18328       -- verify consistency.
18329       ------------------------------------------------------------------------
18330       IF (p_invoice_lines_rec.quantity_invoiced is NOT NULL AND
18331           p_invoice_lines_rec.unit_price is NOT NULL AND
18332           p_invoice_lines_rec.amount is NOT NULL AND
18333           p_invoice_lines_rec.amount <> ap_utilities_pkg.ap_round_currency(
18334                  p_invoice_lines_rec.quantity_invoiced *
18335                  p_invoice_lines_rec.unit_price,
18336                  p_invoice_rec.invoice_currency_code)) THEN
18337         debug_info :=
18338           '(Check Qty UOM non PO 4d) Verify consistency in qty information';
18339         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18340           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18341                                         debug_info);
18342         End if;
18343         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18344                 AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18345                 p_invoice_lines_rec.invoice_line_id,
18346                'INCONSISTENT QTY RELATED INFO',
18347                 p_default_last_updated_by,
18348                 p_default_last_update_login,
18349                 current_calling_sequence) <> TRUE) THEN
18350           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18351             AP_IMPORT_UTILITIES_PKG.Print(
18352               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18353               'insert_rejections<-'||current_calling_sequence);
18354           END IF;
18355           RAISE qty_uom_check_failure;
18356         END IF;
18357         l_current_invoice_status := 'N';
18358       END IF;
18359 
18360       ------------------------------------------------------------------------
18361       -- Step 4e
18362       -- Verify unit of measure provided is valid.
18363       --
18364       ------------------------------------------------------------------------
18365       debug_info :=
18366         '(Check Qty UOM non PO 4e) Verify unit of measure is valid';
18367       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18368         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18369                                       debug_info);
18370       END IF;
18371       BEGIN
18372         SELECT 'Valid UOM'
18373           INTO l_uom_is_valid
18374           FROM mtl_units_of_measure
18375          WHERE unit_of_measure = p_invoice_lines_rec.unit_of_meas_lookup_code
18376            AND AP_IMPORT_INVOICES_PKG.g_inv_sysdate
18377             < nvl(disable_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate + 1) ;
18378       EXCEPTION
18379         WHEN no_data_found THEN
18380           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18381               AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18382               p_invoice_lines_rec.invoice_line_id,
18383               'INVALID UOM',
18384                p_default_last_updated_by,
18385                p_default_last_update_login,
18386                current_calling_sequence) <> TRUE) THEN
18387             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18388               AP_IMPORT_UTILITIES_PKG.Print(
18389                 AP_IMPORT_INVOICES_PKG.g_debug_switch,
18390                'insert_rejections<-'||current_calling_sequence);
18391             END IF;
18392             RAISE qty_uom_check_failure;
18393           END IF;
18394           l_current_invoice_status := 'N';
18395       END;
18396 
18397     END IF; -- line type is ITEM and unit of measure is not null
18398   END IF; -- po header id or rcv transaction id are not null
18399 
18400   p_current_invoice_status := l_current_invoice_status;
18401   RETURN (TRUE);
18402 
18403 EXCEPTION
18404   WHEN OTHERS THEN
18405     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18406       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18407                                     debug_info);
18408     END IF;
18409 
18410     IF (SQLCODE < 0) then
18411       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
18412         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18413                                       SQLERRM);
18414       END IF;
18415     END IF;
18416     RETURN(FALSE);
18417 
18418 END v_check_qty_uom_non_po;
18419 
18420 
18421 -----------------------------------------------------------------------------
18422 -- This function is used to validate line level awt group information.
18423 -----------------------------------------------------------------------------
18424 FUNCTION v_check_invalid_line_awt_group (
18425    p_invoice_rec          IN     AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
18426    p_invoice_lines_rec    IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18427    p_default_last_updated_by     IN            NUMBER,
18428    p_default_last_update_login   IN            NUMBER,
18429    p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
18430    p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
18431 IS
18432    awt_group_check_failure       EXCEPTION;
18433    l_current_invoice_status      VARCHAR2(1) := 'Y';
18434    l_awt_group_id                NUMBER;
18435    l_awt_group_id_per_name       NUMBER;
18436    l_inactive_date               DATE;
18437    l_inactive_date_per_name      DATE;
18438    current_calling_sequence      VARCHAR2(2000);
18439    debug_info                    VARCHAR2(500);
18440 
18441 BEGIN
18442   -- Update the calling sequence
18443   --
18444   current_calling_sequence :=
18445       'AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_awt_group<-'
18446       ||P_calling_sequence;
18447 
18448   IF p_invoice_lines_rec.awt_group_id is not null THEN
18449     --validate awt_group_id
18450     SELECT group_id, inactive_date
18451       INTO l_awt_group_id, l_inactive_date
18452       FROM ap_awt_groups
18453      WHERE group_id = p_invoice_lines_rec.awt_group_id;
18454   END IF;
18455 
18456   IF (p_invoice_lines_rec.awt_group_name is NOT NULL) THEN
18457     --validate awt group name and retrieve awt group id
18458     SELECT group_id, inactive_date
18459       INTO l_awt_group_id_per_name, l_inactive_date_per_name
18460       FROM ap_awt_groups
18461      WHERE name = p_invoice_lines_rec.awt_group_name;
18462   END IF;
18463 
18464   IF (l_awt_group_id is NOT NULL) AND
18465      (l_awt_group_id_per_name is NOT NULL) AND
18466      (l_awt_group_id <> l_awt_group_id_per_name) THEN
18467 
18468     --------------------------------------------------------------------------
18469     -- Step 1
18470     -- Check for AWT Group Id and Group Name Inconsistency.
18471     --------------------------------------------------------------------------
18472     debug_info := '(Check AWT Group 1) Check for AWT Group Id and Group Name '
18473                   ||'Inconsistency.';
18474     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18475       AP_IMPORT_UTILITIES_PKG.Print(
18476         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18477     END IF;
18478 
18479     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18480         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18481          p_invoice_lines_rec.invoice_line_id,
18482         'INCONSISTENT AWT GROUP',
18483          p_default_last_updated_by,
18484          p_default_last_update_login,
18485          current_calling_sequence) <> TRUE) THEN
18486       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18487         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18488           'insert_rejections<-'||current_calling_sequence);
18489       END IF;
18490       RAISE awt_group_check_failure;
18491     END IF;
18492     l_current_invoice_status := 'N';
18493   ELSE
18494     --------------------------------------------------------------------------
18495     -- Step 2
18496     -- Check for Inactive AWT Group
18497     --------------------------------------------------------------------------
18498     debug_info := '(Check AWT Group 2) Check for Inactive AWT Group';
18499     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18500       AP_IMPORT_UTILITIES_PKG.Print(
18501         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18502     END IF;
18503 
18504     IF ((l_awt_group_id IS NOT NULL AND
18505          l_awt_group_id_per_name IS NOT NULL) OR
18506         (l_awt_group_id IS NOT NULL AND
18507          l_awt_group_id_per_name IS NULL)) THEN
18508       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
18509        NVL(l_inactive_date,
18510            AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
18511     --------------------------------------------------------------
18512         -- inactive AWT group (as per id)
18513         --------------------------------------------------------------
18514         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18515              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18516               p_invoice_lines_rec.invoice_line_id,
18517              'INACTIVE AWT GROUP',
18518               p_default_last_updated_by,
18519               p_default_last_update_login,
18520               current_calling_sequence) <> TRUE) THEN
18521           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18522             AP_IMPORT_UTILITIES_PKG.Print(
18523               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18524               'insert_rejections<-'||current_calling_sequence);
18525           END IF;
18526           RAISE awt_group_check_failure;
18527         END IF;
18528         l_current_invoice_status := 'N';
18529       END IF;
18530     ELSIF ((l_awt_group_id is NULL) AND
18531            (l_awt_group_id_per_name is NOT NULL)) THEN
18532       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
18533             nvl(l_inactive_date_per_name,
18534                 AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
18535         ---------------------------------------------------------------
18536         -- inactive AWT group (per name)
18537         --
18538         ---------------------------------------------------------------
18539         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18540              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18541               p_invoice_lines_rec.invoice_line_id,
18542              'INACTIVE AWT GROUP',
18543               p_default_last_updated_by,
18544               p_default_last_update_login,
18545               current_calling_sequence) <> TRUE) THEN
18546           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18547             AP_IMPORT_UTILITIES_PKG.Print(
18548               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18549               'insert_rejections<-'||current_calling_sequence);
18550           END IF;
18551           RAISE awt_group_check_failure;
18552         END IF;
18553         l_current_invoice_status := 'N';
18554       END IF;
18555     END IF;
18556   END IF; -- inconsistent awt group
18557 
18558   IF (l_current_invoice_status <> 'N' AND
18559       p_invoice_lines_rec.awt_group_id IS NULL) THEN
18560     IF (l_awt_group_id_per_name is not null) THEN
18561       p_invoice_lines_rec.awt_group_id := l_awt_group_id_per_name;
18562     ELSIF (p_invoice_rec.awt_group_id is not null) THEN
18563       p_invoice_lines_rec.awt_group_id := p_invoice_rec.awt_group_id;
18564     END IF;
18565   END IF;
18566   p_current_invoice_status := l_current_invoice_status;
18567   RETURN (TRUE);
18568 
18569 
18570 EXCEPTION
18571   WHEN no_data_found THEN
18572     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18573        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18574         p_invoice_lines_rec.invoice_line_id,
18575        'INVALID AWT GROUP',
18576         p_default_last_updated_by,
18577         p_default_last_update_login,
18578         current_calling_sequence) <> TRUE) THEN
18579       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18580         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18581           'insert_rejections<-'||current_calling_sequence);
18582       END IF;
18583       RAISE awt_group_check_failure;
18584     END IF;
18585     l_current_invoice_status := 'N';
18586     p_current_invoice_status := l_current_invoice_status;
18587     RETURN (TRUE);
18588 
18589   WHEN OTHERS THEN
18590     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18591       AP_IMPORT_UTILITIES_PKG.Print(
18592         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18593     END IF;
18594 
18595     IF (SQLCODE < 0) THEN
18596       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18597         AP_IMPORT_UTILITIES_PKG.Print(
18598           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
18599       END IF;
18600     END IF;
18601     RETURN(FALSE);
18602 
18603 END v_check_invalid_line_awt_group;
18604 
18605     --bug6639866
18606 ----------------------------------------------------------------------------
18607 -- This function is used to validate line level pay awt group information.
18608 -----------------------------------------------------------------------------
18609 FUNCTION v_check_invalid_line_pay_awt_g (
18610    p_invoice_rec          IN     AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
18611    p_invoice_lines_rec    IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18612    p_default_last_updated_by     IN            NUMBER,
18613    p_default_last_update_login   IN            NUMBER,
18614    p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
18615    p_calling_sequence            IN            VARCHAR2) RETURN BOOLEAN
18616 IS
18617    pay_awt_group_check_failure       EXCEPTION;
18618    l_current_invoice_status      VARCHAR2(1) := 'Y';
18619    l_pay_awt_group_id                NUMBER;
18620    l_pay_awt_group_id_per_name       NUMBER;
18621    l_inactive_date               DATE;
18622    l_inactive_date_per_name      DATE;
18623    current_calling_sequence      VARCHAR2(2000);
18624    debug_info                    VARCHAR2(500);
18625 
18626 BEGIN
18627   -- Update the calling sequence
18628   --
18629   current_calling_sequence :=
18630       'AP_IMPORT_VALIDATION_PKG.v_check_invalid_line_pay_awt_g<-'
18631       ||P_calling_sequence;
18632 
18633   IF p_invoice_lines_rec.pay_awt_group_id is not null THEN
18634     --validate pay_awt_group_id
18635     SELECT group_id, inactive_date
18636       INTO l_pay_awt_group_id, l_inactive_date
18637       FROM ap_awt_groups
18638      WHERE group_id = p_invoice_lines_rec.pay_awt_group_id;
18639   END IF;
18640 
18641   IF (p_invoice_lines_rec.pay_awt_group_name is NOT NULL) THEN
18642  --validate pay awt group name and retrieve pay awt group id
18643     SELECT group_id, inactive_date
18644       INTO l_pay_awt_group_id_per_name, l_inactive_date_per_name
18645       FROM ap_awt_groups
18646      WHERE name = p_invoice_lines_rec.pay_awt_group_name;
18647   END IF;
18648 
18649   IF (l_pay_awt_group_id is NOT NULL) AND
18650      (l_pay_awt_group_id_per_name is NOT NULL) AND
18651      (l_pay_awt_group_id <> l_pay_awt_group_id_per_name) THEN
18652 
18653     --------------------------------------------------------------------------
18654     -- Step 1
18655     -- Check for Pay AWT Group Id and Pay Group Name Inconsistency.
18656     --------------------------------------------------------------------------
18657     debug_info := '(Check Pay AWT Group 1) Check for Pay AWT Group Id and Pay Group Name '
18658                   ||'Inconsistency.';
18659     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18660       AP_IMPORT_UTILITIES_PKG.Print(
18661         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18662     END IF;
18663 
18664     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18665         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18666          p_invoice_lines_rec.invoice_line_id,
18667         'INCONSISTENT PAY AWT GROUP',
18668          p_default_last_updated_by,
18669          p_default_last_update_login,
18670          current_calling_sequence) <> TRUE) THEN
18671       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18672         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18673           'insert_rejections<-'||current_calling_sequence);
18674       END IF;
18675       RAISE pay_awt_group_check_failure;
18676     END IF;
18677  l_current_invoice_status := 'N';
18678   ELSE
18679     --------------------------------------------------------------------------
18680     -- Step 2
18681     -- Check for Inactive Pay AWT Group
18682     --------------------------------------------------------------------------
18683     debug_info := '(Check Pay AWT Group 2) Check for Inactive Pay AWT Group';
18684     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18685       AP_IMPORT_UTILITIES_PKG.Print(
18686         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18687     END IF;
18688 
18689     IF ((l_pay_awt_group_id IS NOT NULL AND
18690          l_pay_awt_group_id_per_name IS NOT NULL) OR
18691         (l_pay_awt_group_id IS NOT NULL AND
18692          l_pay_awt_group_id_per_name IS NULL)) THEN
18693       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
18694        NVL(l_inactive_date,
18695            AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
18696         --------------------------------------------------------------
18697         -- inactive pay AWT group (as per id)
18698         --------------------------------------------------------------
18699         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18700              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18701               p_invoice_lines_rec.invoice_line_id,
18702              'INACTIVE PAY AWT GROUP',
18703               p_default_last_updated_by,
18704               p_default_last_update_login,
18705               current_calling_sequence) <> TRUE) THEN
18706           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18707             AP_IMPORT_UTILITIES_PKG.Print(
18708               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18709               'insert_rejections<-'||current_calling_sequence);
18710           END IF;
18711           RAISE pay_awt_group_check_failure;
18712         END IF;
18713         l_current_invoice_status := 'N';
18714       END IF;
18715     ELSIF ((l_pay_awt_group_id is NULL) AND
18716            (l_pay_awt_group_id_per_name is NOT NULL)) THEN
18717       IF AP_IMPORT_INVOICES_PKG.g_inv_sysdate >=
18718             nvl(l_inactive_date_per_name,
18719                 AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) THEN
18720         ---------------------------------------------------------------
18721         -- inactive pay AWT group (per name)
18722         --
18723         ---------------------------------------------------------------
18724         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18725              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18726               p_invoice_lines_rec.invoice_line_id,
18727              'INACTIVE PAY AWT GROUP',
18728               p_default_last_updated_by,
18729               p_default_last_update_login,
18730               current_calling_sequence) <> TRUE) THEN
18731           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18732             AP_IMPORT_UTILITIES_PKG.Print(
18733               AP_IMPORT_INVOICES_PKG.g_debug_switch,
18734               'insert_rejections<-'||current_calling_sequence);
18735           END IF;
18736           RAISE pay_awt_group_check_failure;
18737         END IF;
18738         l_current_invoice_status := 'N';
18739       END IF;
18740     END IF;
18741   END IF; -- inconsistent pay awt group
18742 
18743   IF (l_current_invoice_status <> 'N' AND
18744       p_invoice_lines_rec.pay_awt_group_id IS NULL) THEN
18745     IF (l_pay_awt_group_id_per_name is not null) THEN
18746       p_invoice_lines_rec.pay_awt_group_id := l_pay_awt_group_id_per_name;
18747  ELSIF (p_invoice_rec.pay_awt_group_id is not null) THEN
18748       p_invoice_lines_rec.pay_awt_group_id := p_invoice_rec.pay_awt_group_id;
18749     END IF;
18750   END IF;
18751   p_current_invoice_status := l_current_invoice_status;
18752   RETURN (TRUE);
18753 
18754 
18755 EXCEPTION
18756   WHEN no_data_found THEN
18757     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18758        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18759         p_invoice_lines_rec.invoice_line_id,
18760        'INVALID PAY AWT GROUP',
18761         p_default_last_updated_by,
18762         p_default_last_update_login,
18763         current_calling_sequence) <> TRUE) THEN
18764       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18765         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18766           'insert_rejections<-'||current_calling_sequence);
18767       END IF;
18768       RAISE pay_awt_group_check_failure;
18769     END IF;
18770     l_current_invoice_status := 'N';
18771     p_current_invoice_status := l_current_invoice_status;
18772     RETURN (TRUE);
18773 
18774   WHEN OTHERS THEN
18775     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18776       AP_IMPORT_UTILITIES_PKG.Print(
18777         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18778     END IF;
18779 
18780     IF (SQLCODE < 0) THEN
18781       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18782           AP_IMPORT_UTILITIES_PKG.Print(
18783           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
18784       END IF;
18785     END IF;
18786     RETURN(FALSE);
18787 
18788 END v_check_invalid_line_pay_awt_g;
18789 
18790 
18791 -----------------------------------------------------------------------------
18792 -- This function is used to validate that there is no duplicate line number
18793 -----------------------------------------------------------------------------
18794 FUNCTION v_check_duplicate_line_num (
18795    p_invoice_rec     IN            AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
18796    p_invoice_lines_rec  IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18797    p_default_last_updated_by      IN            NUMBER,
18798    p_default_last_update_login    IN            NUMBER,
18799    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
18800    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
18801 IS
18802 
18803 line_num_check_failure        EXCEPTION;
18804 l_line_count                   NUMBER;
18805 l_current_invoice_status    VARCHAR2(1) := 'Y';
18806 current_calling_sequence    VARCHAR2(2000);
18807 debug_info                  VARCHAR2(500);
18808 
18809 BEGIN
18810   -- Update the calling sequence
18811   --
18812   current_calling_sequence :=
18813       'AP_IMPORT_VALIDATION_PKG.v_check_duplicate_line_num<-'
18814      ||P_calling_sequence;
18815 
18816   IF (p_invoice_lines_rec.line_number is NOT NULL) THEN
18817 
18818     --------------------------------------------------------------------------
18819     -- Step 1
18820     -- Check for Duplicate Line NUMBER.
18821     --------------------------------------------------------------------------
18822     debug_info := '(Check Duplicate Line Number 1) Check for Duplicate '
18823                   ||'Line Number.';
18824     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18825       AP_IMPORT_UTILITIES_PKG.Print(
18826         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18827     END IF;
18828 
18829     SELECT count(*)
18830       INTO l_line_count
18831       FROM ap_invoice_lines_interface
18832      WHERE invoice_id = p_invoice_rec.invoice_id
18833        AND line_number = p_invoice_lines_rec.line_number;
18834 
18835     IF (l_line_count > 1) THEN
18836       debug_info := '(Check Duplicate Line Number 2) Duplicate Line '
18837                     ||'Number Found.';
18838       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18839         AP_IMPORT_UTILITIES_PKG.Print(
18840           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18841       END IF;
18842 
18843       -- bug 2581097 added context for XML GATEWAY
18844       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18845         AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18846            p_invoice_lines_rec.invoice_line_id,
18847            'DUPLICATE LINE NUMBER',
18848            p_default_last_updated_by,
18849            p_default_last_update_login,
18850            current_calling_sequence,
18851            'Y',
18852            'INVOICE LINE NUMBER',
18853            p_invoice_lines_rec.line_number) <> TRUE) THEN
18854         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18855           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18856             'insert_rejections<-'||current_calling_sequence);
18857         END IF;
18858         RAISE line_num_check_failure;
18859       END IF;
18860       l_current_invoice_status := 'N';
18861     END IF;
18862   END IF;
18863 
18864   p_current_invoice_status := l_current_invoice_status;
18865   RETURN (TRUE);
18866 EXCEPTION
18867   WHEN OTHERS THEN
18868     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18869       AP_IMPORT_UTILITIES_PKG.Print(
18870         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18871     END IF;
18872 
18873     IF (SQLCODE < 0) THEN
18874       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18875         AP_IMPORT_UTILITIES_PKG.Print(
18876           AP_IMPORT_INVOICES_PKG.g_debug_switch,SQLERRM);
18877       END IF;
18878     END IF;
18879     RETURN(FALSE);
18880 
18881 END v_check_duplicate_line_num;
18882 
18883 
18884 -----------------------------------------------------------------------------
18885 -- This function is used to validate that miscellaneous line level information
18886 -----------------------------------------------------------------------------
18887 FUNCTION v_check_misc_line_info (
18888    p_invoice_rec          		  IN
18889 						AP_IMPORT_INVOICES_PKG.r_invoice_info_rec, --bug 7599916
18890    p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
18891    p_default_last_updated_by      IN            NUMBER,
18892    p_default_last_update_login    IN            NUMBER,
18893    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
18894    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
18895 
18896 IS
18897 
18898 misc_line_info_failure        EXCEPTION;
18899 l_valid_info                VARCHAR2(1);
18900 l_current_invoice_status    VARCHAR2(1) := 'Y';
18901 current_calling_sequence    VARCHAR2(2000);
18902 debug_info                  VARCHAR2(500);
18903 -- Bug 5572876. Caching Income Tax Type and Income Tax Region
18904 l_key                            VARCHAR2(1000);
18905 l_numof_values                   NUMBER;
18906 l_valueOut                   fnd_plsql_cache.generic_cache_value_type;
18907 l_values                     fnd_plsql_cache.generic_cache_values_type;
18908 l_ret_code                      VARCHAR2(1);
18909 l_exception                     VARCHAR2(10);
18910 l_key1                          VARCHAR2(1000);
18911 l_numof_values1                 NUMBER;
18912 l_valueOut1                  fnd_plsql_cache.generic_cache_value_type;
18913 l_values1                    fnd_plsql_cache.generic_cache_values_type;
18914 l_ret_code1                  VARCHAR2(1);
18915 l_exception1                    VARCHAR2(10);
18916 l_income_tax_type               ap_income_tax_types.income_tax_type%TYPE;
18917 l_income_tax_region             ap_income_tax_regions.region_short_name%TYPE;
18918 
18919         -- Bug 7599916
18920 	Cursor c_type_1099(c_vendor_id NUMBER) Is
18921 	Select pov.type_1099
18922 	From   po_vendors 		   pov
18923 	Where  pov.vendor_id    = c_vendor_id;
18924 	-- Bug 7599916
18925 
18926 BEGIN
18927   -- Update the calling sequence
18928   --
18929   current_calling_sequence :=
18930     'AP_IMPORT_VALIDATION_PKG.v_check_misc_line_info<-'
18931     ||P_calling_sequence;
18932 
18933   --Retropricing
18934   IF (nvl(p_invoice_lines_rec.line_type_lookup_code,'DUMMY')
18935      NOT IN ('FREIGHT','ITEM','MISCELLANEOUS','TAX','AWT', 'RETROITEM', 'RETROTAX')) THEN
18936 
18937     --------------------------------------------------------------------------
18938     -- Step 1
18939     -- Check for Invalid Line type lookup code.
18940     --------------------------------------------------------------------------
18941     debug_info :=
18942        '(Check Misc Line Info 1) Check for Invalid Line type lookup code.';
18943     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18944       AP_IMPORT_UTILITIES_PKG.Print(
18945         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
18946     END IF;
18947 
18948     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18949       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18950          p_invoice_lines_rec.invoice_line_id,
18951          'INVALID LINE TYPE LOOKUP',
18952          p_default_last_updated_by,
18953          p_default_last_update_login,
18954          current_calling_sequence) <> TRUE) THEN
18955       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18956         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18957           'insert_rejections<-' ||current_calling_sequence);
18958       END IF;
18959       RAISE misc_line_info_failure;
18960     END IF;
18961 
18962     l_current_invoice_status := 'N';
18963 
18964   ELSIF (p_invoice_lines_rec.line_type_lookup_code ='AWT') THEN
18965 
18966     ----------------------------------------------------------------------
18967     -- Step 2
18968     -- Line type lookup code cannot be AWT
18969     ----------------------------------------------------------------------
18970     debug_info := '(Check Misc Line Info 2) Line type lookup code '
18971                   ||'cannot be AWT';
18972     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18973       AP_IMPORT_UTILITIES_PKG.Print(
18974         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
18975     END IF;
18976 
18977     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
18978       AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
18979        p_invoice_lines_rec.invoice_line_id,
18980        'LINE TYPE CANNOT BE AWT',
18981        p_default_last_updated_by,
18982        p_default_last_update_login,
18983        current_calling_sequence) <> TRUE) THEN
18984       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
18985         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
18986           'insert_rejections<-' ||current_calling_sequence);
18987       END IF;
18988       RAISE misc_line_info_failure;
18989     END IF;
18990     l_current_invoice_status := 'N';
18991   END IF; -- line type
18992 
18993     -- Bug 7599916
18994 	IF (p_invoice_lines_rec.type_1099 is NULL) THEN
18995 	--------------------------------------------------------------------------
18996     -- Step 3.1
18997     -- defaulting type_1099 from supplier if null in interface table
18998     --------------------------------------------------------------------------
18999 
19000 	debug_info := '(Check Misc Line Info 3) Defaulting type 1099 from
19001 	supplier';
19002     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19003       AP_IMPORT_UTILITIES_PKG.Print(
19004         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
19005     END IF;
19006 
19007 	Open  c_type_1099(p_invoice_rec.vendor_id);
19008 	Fetch c_type_1099 Into p_invoice_lines_rec.type_1099;
19009 	Close c_type_1099;
19010 
19011 	END IF;
19012 	-- Bug 7599916
19013 
19014    IF (p_invoice_lines_rec.type_1099 is NOT NULL) THEN
19015 
19016     --------------------------------------------------------------------------
19017     -- Step 3.2
19018     -- Invalid type_1099
19019     --------------------------------------------------------------------------
19020     debug_info := '(Check Misc Line Info 3) Check Type 1099';
19021     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19022       AP_IMPORT_UTILITIES_PKG.Print(
19023         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
19024     END IF;
19025 
19026     -- Invalid Info
19027 
19028     l_key := p_invoice_lines_rec.type_1099;
19029 
19030     fnd_plsql_cache.generic_1tom_get_values(
19031               AP_IMPORT_INVOICES_PKG.lg_incometax_controller,
19032               AP_IMPORT_INVOICES_PKG.lg_incometax_storage,
19033               l_key,
19034               l_numof_values,
19035               l_values,
19036               l_ret_code);
19037 
19038     IF l_ret_code = '1' THEN --  means l_key found in cache
19039       l_income_tax_type := l_values(1).varchar2_1;
19040       l_exception   := l_values(1).varchar2_2;
19041       IF l_exception = 'TRUE' THEN
19042         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19043           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19044            p_invoice_lines_rec.invoice_line_id,
19045           'INVALID TYPE 1099',
19046            p_default_last_updated_by,
19047            p_default_last_update_login,
19048            current_calling_sequence) <> TRUE) THEN
19049           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19050             AP_IMPORT_UTILITIES_PKG.Print(
19051                AP_IMPORT_INVOICES_PKG.g_debug_switch,
19052               'insert_rejections<-' ||current_calling_sequence);
19053           END IF;
19054            RAISE misc_line_info_failure;
19055         END IF;
19056 
19057         l_current_invoice_status := 'N';
19058       END IF;
19059 
19060     ELSE -- IF l_key not found in cache(l_ret_code other than 1) .. cache it
19061       debug_info := '(Check Misc Line Info 3.1) Check Type 1099 in Else';
19062       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19063         AP_IMPORT_UTILITIES_PKG.Print(
19064           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
19065       END IF;
19066 
19067        BEGIN
19068         SELECT income_tax_type
19069         INTO l_income_tax_type
19070         FROM ap_income_tax_types
19071         WHERE income_tax_type = p_invoice_lines_rec.type_1099
19072          AND AP_IMPORT_INVOICES_PKG.g_inv_sysdate
19073            < NVL(inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate+1) ;
19074 
19075         l_exception           := 'FALSE';
19076         l_valueOut.varchar2_1 := l_income_tax_type;
19077         l_valueOut.varchar2_2 := l_exception;
19078         l_values(1)           := l_valueOut;
19079         l_numof_values        := 1;
19080 
19081         fnd_plsql_cache.generic_1tom_put_values(
19082                   AP_IMPORT_INVOICES_PKG.lg_incometax_controller,
19083                   AP_IMPORT_INVOICES_PKG.lg_incometax_storage,
19084                   l_key,
19085                   l_numof_values,
19086                   l_values);
19087 
19088       EXCEPTION
19089         WHEN NO_DATA_FOUND THEN
19090           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19091             AP_IMPORT_UTILITIES_PKG.Print(
19092             AP_IMPORT_INVOICES_PKG.g_debug_switch,
19093               '(v_check_misc_line_info 3) Invalid Type 1099');
19094           END IF;
19095 
19096           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19097             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19098             p_invoice_lines_rec.invoice_line_id,
19099            'INVALID TYPE 1099',
19100             p_default_last_updated_by,
19101             p_default_last_update_login,
19102             current_calling_sequence) <> TRUE) THEN
19103             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19104               AP_IMPORT_UTILITIES_PKG.Print(
19105                AP_IMPORT_INVOICES_PKG.g_debug_switch,
19106               'insert_rejections<-' ||current_calling_sequence);
19107             END IF;
19108             RAISE misc_line_info_failure;
19109           END IF;
19110           --
19111           l_current_invoice_status := 'N';
19112           l_exception              := 'TRUE';
19113           l_valueOut.varchar2_1    := NULL;
19114           l_valueOut.varchar2_2    := l_exception;
19115           l_values(1)              := l_valueOut;
19116           l_numof_values           := 1;
19117 
19118             fnd_plsql_cache.generic_1tom_put_values(
19119                     AP_IMPORT_INVOICES_PKG.lg_incometax_controller,
19120                     AP_IMPORT_INVOICES_PKG.lg_incometax_storage,
19121                     l_key,
19122                     l_numof_values,
19123                     l_values);
19124 
19125       END;
19126 
19127     END IF;
19128 
19129   END IF; -- type 1099 is not null
19130 
19131   IF (p_invoice_lines_rec.income_tax_region is NOT NULL) THEN
19132 
19133     --------------------------------------------------------------------------
19134     -- Step 4
19135     -- Invalid income_tax_region
19136     --------------------------------------------------------------------------
19137     debug_info := '(Check Misc Line Info 4) Check income_tax_region';
19138     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19139       AP_IMPORT_UTILITIES_PKG.Print(
19140         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
19141     END IF;
19142 
19143     -- Invalid Info
19144     l_key1 := p_invoice_lines_rec.income_tax_region;
19145 
19146     fnd_plsql_cache.generic_1tom_get_values(
19147               AP_IMPORT_INVOICES_PKG.lg_incometaxr_controller,
19148               AP_IMPORT_INVOICES_PKG.lg_incometaxr_storage,
19149               l_key1,
19150               l_numof_values1,
19151               l_values1,
19152               l_ret_code1);
19153 
19154     IF l_ret_code1 = '1' THEN --  means l_key found in cache
19155       l_income_tax_region := l_values1(1).varchar2_1;
19156       l_exception1   := l_values1(1).varchar2_2;
19157       IF l_exception1 = 'TRUE' THEN
19158         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19159           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19160            p_invoice_lines_rec.invoice_line_id,
19161           'INVALID TAX REGION',
19162            p_default_last_updated_by,
19163            p_default_last_update_login,
19164            current_calling_sequence) <> TRUE) THEN
19165           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19166             AP_IMPORT_UTILITIES_PKG.Print(
19167                AP_IMPORT_INVOICES_PKG.g_debug_switch,
19168               'insert_rejections<-' ||current_calling_sequence);
19169           END IF;
19170           RAISE misc_line_info_failure;
19171         END IF;
19172 
19173         l_current_invoice_status := 'N';
19174       END IF;
19175 
19176     ELSE
19177       debug_info := '(Check Misc Line Info 4.1) Check income_tax_region in Else';
19178       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19179         AP_IMPORT_UTILITIES_PKG.Print(
19180           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
19181       END IF;
19182 
19183       BEGIN
19184         SELECT region_short_name
19185         INTO l_income_tax_region
19186         FROM ap_income_tax_regions
19187         WHERE region_short_name = p_invoice_lines_rec.income_tax_region
19188          AND AP_IMPORT_INVOICES_PKG.g_inv_sysdate
19189         BETWEEN NVL(active_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate) AND
19190         NVL(inactive_date, AP_IMPORT_INVOICES_PKG.g_inv_sysdate);
19191 
19192         l_exception1           := 'FALSE';
19193         l_valueOut1.varchar2_1 := l_income_tax_region;
19194         l_valueOut1.varchar2_2 := l_exception1;
19195         l_values1(1)           := l_valueOut1;
19196         l_numof_values1        := 1;
19197 
19198         fnd_plsql_cache.generic_1tom_put_values(
19199                   AP_IMPORT_INVOICES_PKG.lg_incometaxr_controller,
19200                   AP_IMPORT_INVOICES_PKG.lg_incometaxr_storage,
19201                   l_key1,
19202                   l_numof_values1,
19203                   l_values1);
19204 
19205       EXCEPTION
19206         WHEN NO_DATA_FOUND THEN
19207           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19208             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19209             '(v_check_misc_line_info 4) Invalid income tax region');
19210           END IF;
19211           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19212             AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19213              p_invoice_lines_rec.invoice_line_id,
19214             'INVALID TAX REGION',
19215              p_default_last_updated_by,
19216              p_default_last_update_login,
19217              current_calling_sequence) <> TRUE) THEN
19218             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19219               AP_IMPORT_UTILITIES_PKG.Print(
19220               AP_IMPORT_INVOICES_PKG.g_debug_switch,
19221                 'insert_rejections<-' ||current_calling_sequence);
19222             END IF;
19223             RAISE misc_line_info_failure;
19224           END IF;
19225           l_current_invoice_status := 'N';
19226           l_exception1             := 'TRUE';
19227           l_valueOut1.varchar2_1   := NULL;
19228           l_valueOut1.varchar2_2   := l_exception1;
19229           l_values1(1)             := l_valueOut1;
19230           l_numof_values1          := 1;
19231 
19232           fnd_plsql_cache.generic_1tom_put_values(
19233                     AP_IMPORT_INVOICES_PKG.lg_incometaxr_controller,
19234                     AP_IMPORT_INVOICES_PKG.lg_incometaxr_storage,
19235                     l_key1,
19236                     l_numof_values1,
19237                     l_values1);
19238 
19239       END;
19240 
19241     END IF;
19242 
19243   END IF;
19244 
19245   p_current_invoice_status := l_current_invoice_status;
19246   RETURN (TRUE);
19247 
19248 EXCEPTION
19249   WHEN OTHERS THEN
19250     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19251       AP_IMPORT_UTILITIES_PKG.Print(
19252         AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
19253     END IF;
19254 
19255     IF (SQLCODE < 0) THEN
19256       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19257         AP_IMPORT_UTILITIES_PKG.Print(
19258           AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
19259       END IF;
19260     END IF;
19261     RETURN(FALSE);
19262 
19263 END v_check_misc_line_info;
19264 
19265 ---------------------------------------------------------------------------------
19266 -- This function verifies proration of non item lines
19267 --
19268 FUNCTION v_check_prorate_info (
19269    p_invoice_rec                  IN
19270      AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
19271    p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
19272    p_default_last_updated_by      IN            NUMBER,
19273    p_default_last_update_login    IN            NUMBER,
19274    p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
19275    p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
19276 
19277 IS
19278 
19279 prorate_line_info_failure       EXCEPTION;
19280 l_item_line_total               NUMBER;
19281 l_count_non_item_lines          NUMBER := 0;
19282 l_current_invoice_status    VARCHAR2(1) := 'Y';
19283 current_calling_sequence      VARCHAR2(2000);
19284 debug_info                   VARCHAR2(500);
19285 
19286 BEGIN
19287   -- Update the calling sequence
19288   --
19289   current_calling_sequence :=
19290     'AP_IMPORT_VALIDATION_PKG.v_check_prorate_info<-' ||P_calling_sequence;
19291 
19292   ---------------------------------------------------------------------------
19293   -- Step 1
19294   -- Sum of lines to prorate against cannot be 0
19295   ---------------------------------------------------------------------------
19296   debug_info := '(Check Prorate Info 1) Checking the total dist amount to be '
19297                ||'prorated';
19298   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19299    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19300                                  debug_info);
19301   END IF;
19302 
19303   SELECT   SUM(nvl(AIL.amount,0))
19304     INTO   l_item_line_total
19305     FROM   ap_invoice_lines_interface AIL
19306    WHERE   AIL.invoice_id = p_invoice_rec.invoice_id
19307      AND   ((line_group_number = p_invoice_lines_rec.line_group_number AND
19308              p_invoice_lines_rec.line_group_number IS NOT NULL)         OR
19309             p_invoice_lines_rec.line_group_number is NULL)
19310      AND    line_type_lookup_code = 'ITEM';
19311 
19312   IF (l_item_line_total = 0 ) THEN
19313     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19314         AP_IMPORT_INVOICES_PKG.g_invoices_table,
19315      p_invoice_lines_rec.invoice_line_id,
19316         'CANNOT PRORATE TO ZERO',
19317      p_default_last_updated_by,
19318      p_default_last_update_login,
19319      current_calling_sequence) <> TRUE ) THEN
19320       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19321         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19322            'insert_rejections<- '||current_calling_sequence);
19323       END IF;
19324       RAISE prorate_line_info_failure;
19325     END IF;
19326     l_current_invoice_status := 'N';
19327   END IF; -- Total of amount for item lines to prorate across is 0
19328 
19329   ---------------------------------------------------------------------------
19330   -- Step 2
19331   -- Prorating across non-item lines is not allowed
19332   ---------------------------------------------------------------------------
19333   debug_info := '(Check Prorate Info 2) Checking lines to prorate across.';
19334   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19335    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19336                                  debug_info);
19337   END IF;
19338 
19339   IF (p_invoice_lines_rec.line_group_number IS NOT NULL) THEN
19340 
19341     SELECT   COUNT(*)
19342       INTO   l_count_non_item_lines
19343       FROM   ap_invoice_lines_interface AIL
19344      WHERE   AIL.invoice_id = p_invoice_rec.invoice_id
19345        AND   line_group_number = p_invoice_lines_rec.line_group_number
19346        AND   line_type_lookup_code <> 'ITEM';
19347 
19348     -- If number of lines other than Item is more than 1 (1 is itself)
19349     -- raise rejection
19350     IF (l_count_non_item_lines > 1) THEN
19351       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19352           AP_IMPORT_INVOICES_PKG.g_invoices_table,
19353        p_invoice_lines_rec.invoice_line_id,
19354           'CANNOT PRORATE TO NON ITEM',
19355        p_default_last_updated_by,
19356        p_default_last_update_login,
19357            current_calling_sequence) <> TRUE ) THEN
19358         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19359           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19360              'insert_rejections<- '||current_calling_sequence);
19361         END IF;
19362         RAISE prorate_line_info_failure;
19363       END IF;
19364     END IF; -- count of non item lines is > 1
19365   END IF; -- line group number is not null
19366 
19367   p_current_invoice_status := l_current_invoice_status;
19368   RETURN (TRUE);
19369 
19370 EXCEPTION
19371   WHEN OTHERS THEN
19372     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19373       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19374                                     debug_info);
19375     END IF;
19376 
19377     IF (SQLCODE < 0) THEN
19378       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19379         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19380                                       SQLERRM);
19381       END IF;
19382     END IF;
19383     RETURN(FALSE);
19384 
19385 END v_check_prorate_info;
19386 
19387 -----------------------------------------------------------------------------
19388 -- This function verifies and populates asset information
19389 --
19390 FUNCTION v_check_asset_info (
19391          p_invoice_lines_rec
19392            IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
19393          p_set_of_books_id              IN            NUMBER,
19394          p_asset_book_type              IN            VARCHAR2, -- 5448579
19395          p_default_last_updated_by      IN            NUMBER,
19396          p_default_last_update_login    IN            NUMBER,
19397          p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
19398          p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
19399 IS
19400 
19401 asset_line_info_failure         EXCEPTION;
19402 l_valid_asset_book             VARCHAR2(30);
19403 l_asset_book_count             NUMBER;
19404 l_valid_asset_category         VARCHAR2(30);
19405 l_current_invoice_status        VARCHAR2(1) := 'Y';
19406 current_calling_sequence       VARCHAR2(2000);
19407 debug_info                    VARCHAR2(500);
19408 
19409 BEGIN
19410   -- Update the calling sequence
19411   --
19412   current_calling_sequence := 'AP_IMPORT_UTILITIES_PKG.v_check_asset_ifno<-'
19413                               ||P_calling_sequence;
19414 
19415   -------------------------------------------------------------------------------
19416   -- Step 1 - If line type is other than item and any of the asset fields is
19417   -- populated, reject appropriately.
19418   --
19419   ----------------------------------------------------------------------------
19420   debug_info := '(Check Asset Book 1) Verify asset info not on non-item line';
19421   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19422     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19423                                   debug_info);
19424   END IF;
19425 
19426   --Retropricing
19427   IF (p_invoice_lines_rec.line_type_lookup_code NOT IN ('ITEM', 'RETROITEM')) THEN
19428     IF (p_invoice_lines_rec.serial_number IS NOT NULL) THEN
19429       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19430           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19431            p_invoice_lines_rec.invoice_line_id,
19432            'INVALID SERIAL NUMBER INFO',
19433            p_default_last_updated_by,
19434            p_default_last_update_login,
19435            current_calling_sequence) <> TRUE ) THEN
19436         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19437           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19438              'insert_rejections<- '||current_calling_sequence);
19439         END IF;
19440         RAISE asset_line_info_failure;
19441       END IF;
19442       l_current_invoice_status := 'N';
19443     END IF; -- Serial number is not null
19444 
19445     IF (p_invoice_lines_rec.manufacturer IS NOT NULL) THEN
19446       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19447           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19448            p_invoice_lines_rec.invoice_line_id,
19449            'INVALID MANUFACTURER INFO',
19450            p_default_last_updated_by,
19451            p_default_last_update_login,
19452            current_calling_sequence) <> TRUE ) THEN
19453         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19454           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19455             'insert_rejections<- '||current_calling_sequence);
19456         END IF;
19457         RAISE asset_line_info_failure;
19458       END IF;
19459       l_current_invoice_status := 'N';
19460     END IF; -- Manufacturer is not null
19461 
19462     IF (p_invoice_lines_rec.model_number IS NOT NULL) THEN
19463       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19464           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19465            p_invoice_lines_rec.invoice_line_id,
19466            'INVALID MODEL NUMBER INFO',
19467            p_default_last_updated_by,
19468            p_default_last_update_login,
19469            current_calling_sequence) <> TRUE ) Then
19470         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19471           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19472            'insert_rejections<- '||current_calling_sequence);
19473         END IF;
19474         RAISE asset_line_info_failure;
19475       END IF;
19476       l_current_invoice_status := 'N';
19477     END IF; -- Model Number is not null
19478 
19479     IF (p_invoice_lines_rec.warranty_number is not null) then
19480      IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19481           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19482            p_invoice_lines_rec.invoice_line_id,
19483            'INVALID WARRANTY NUM INFO',
19484            p_default_last_updated_by,
19485            p_default_last_update_login,
19486            current_calling_sequence) <> TRUE ) Then
19487         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19488          AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19489            'insert_rejections<- '||current_calling_sequence);
19490         END IF;
19491         RAISE asset_line_info_failure;
19492       END IF;
19493       l_current_invoice_status := 'N';
19494     END IF; -- Warranty Number is not null
19495 
19496   END IF; -- Line type is other than ITEM, RETROITEM
19497 
19498   ----------------------------------------------------------------------------
19499  -- Step 2 - If asset book type code is populated verify that it is correct.
19500  -- If it is not populated, populate based on set of books if a single asset
19501  -- book is found.
19502  --
19503   ----------------------------------------------------------------------------
19504   debug_info := '(Check Asset Book 2) Verify asset book if not null';
19505   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19506     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19507                                   debug_info);
19508   END IF;
19509 
19510   IF (p_invoice_lines_rec.asset_book_type_code IS NOT NULL) THEN
19511     debug_info := 'Verify Asset Book since it is not null';
19512     BEGIN
19513       SELECT 'Asset Book Found'
19514         INTO l_valid_asset_book
19515         FROM fa_book_controls bc
19516        WHERE bc.set_of_books_id = p_set_of_books_id
19517          AND bc.book_type_code = p_invoice_lines_rec.asset_book_type_code
19518          AND bc.date_ineffective IS NULL;
19519 
19520     EXCEPTION
19521       WHEN no_data_found then
19522        IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19523           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19524            p_invoice_lines_rec.invoice_line_id,
19525            'INVALID ASSET BOOK CODE',
19526            p_default_last_updated_by,
19527            p_default_last_update_login,
19528            current_calling_sequence) <> TRUE ) Then
19529           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19530             AP_IMPORT_UTILITIES_PKG.Print(
19531               AP_IMPORT_INVOICES_PKG.g_debug_switch,
19532                'insert_rejections<- '||current_calling_sequence);
19533           END IF;
19534           RAISE asset_line_info_failure;
19535        END IF;
19536        l_current_invoice_status := 'N';
19537       WHEN OTHERS THEN
19538         RAISE asset_line_info_failure;
19539     END;
19540 
19541   ELSE -- Asset book is null
19542     debug_info := 'Get asset book if null and a single one exists for sob';
19543     -- Bug 5448579
19544     p_invoice_lines_rec.asset_book_type_code  := p_asset_book_type;
19545 
19546   END IF; -- Asset book type code is not null
19547 
19548   ----------------------------------------------------------------------------
19549   -- Step 3 - If asset category is populated, verify that it is appropriate
19550   --
19551   ----------------------------------------------------------------------------
19552   debug_info := '(Check Asset Book 3) Verify asset category if not null';
19553   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19554     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19555                                   debug_info);
19556   End if;
19557 
19558   If (p_invoice_lines_rec.asset_category_id is not null) then
19559     debug_info := 'Verify Asset Category since it is not null';
19560     BEGIN
19561       SELECT 'Asset Category found'
19562         INTO l_valid_asset_category
19563         FROM fa_categories
19564        WHERE category_id = p_invoice_lines_rec.asset_category_id;
19565 
19566     EXCEPTION
19567       WHEN no_data_found then
19568        If (AP_IMPORT_UTILITIES_PKG.insert_rejections(
19569            AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
19570            p_invoice_lines_rec.invoice_line_id,
19571            'INVALID ASSET CATEGORY ID',
19572            p_default_last_updated_by,
19573            p_default_last_update_login,
19574            current_calling_sequence) <> TRUE ) Then
19575           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19576            AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19577              'insert_rejections<- '||current_calling_sequence);
19578           END IF;
19579           RAISE asset_line_info_failure;
19580        END IF;
19581        l_current_invoice_status := 'N';
19582       WHEN OTHERS THEN
19583         RAISE asset_line_info_failure;
19584     END;
19585 
19586   END IF; -- Asset category is not null
19587 
19588   p_current_invoice_status := l_current_invoice_status;
19589   RETURN (TRUE);
19590 EXCEPTION
19591   WHEN OTHERS THEN
19592     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19593       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19594                                     debug_info);
19595     END IF;
19596 
19597     IF (SQLCODE < 0) then
19598       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
19599         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19600                                       SQLERRM);
19601       END IF;
19602     END IF;
19603     RETURN(FALSE);
19604 
19605 END v_check_asset_info;
19606 
19607 /*=============================================================================
19608  |  FUNCTION - V_Check_Tax_Info()
19609  |
19610  |  DESCRIPTION
19611  |      This function will validate the following fields included in the
19612  |      ap_invoices_interface table as part of the eTax Uptake project:
19613  |        control_amount
19614  |        tax_related_invoice_id
19615  |        calc_tax_during_import_flag
19616  |
19617  |      The other tax fields will be validated by the eTax API.  See DLD for
19618  |      details.
19619  |
19620  |  PARAMETERS
19621  |    p_invoice_rec - record for invoice header
19622  |    p_default_last_updated_by - default last updated by
19623  |    p_default_last_update_login - default last update login
19624  |    p_current_invoice_status - return the status of the invoice after the
19625  |                               validation
19626  |    P_calling_sequence -  Calling sequence
19627  |
19628  |  MODIFICATION HISTORY
19629  |    DATE          Author         Action
19630  |    20-JAN-2004   SYIDNER        Created
19631  |
19632  *============================================================================*/
19633 
19634 FUNCTION v_check_tax_info(
19635      p_invoice_rec               IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
19636      p_default_last_updated_by   IN            NUMBER,
19637      p_default_last_update_login IN            NUMBER,
19638      p_current_invoice_status    IN OUT NOCOPY VARCHAR2,
19639      p_calling_sequence          IN            VARCHAR2) RETURN BOOLEAN
19640 IS
19641 
19642   l_current_invoice_status        VARCHAR2(1);
19643   l_reject_code                   VARCHAR2(30);
19644   current_calling_sequence        VARCHAR2(2000);
19645 
19646   debug_info                      VARCHAR2(500);
19647   check_tax_failure               EXCEPTION;
19648 
19649   l_related_inv_id                ap_invoices_all.invoice_id%TYPE;
19650   l_exist_tax_line                ap_invoices_all.invoice_id%TYPE;
19651   l_alloc_not_provided            VARCHAR2(1);
19652   l_tax_lines_cannot_coexist      VARCHAR2(1);
19653   l_tax_found_in_nontax_line      VARCHAR2(1);
19654 
19655 BEGIN
19656 
19657   current_calling_sequence :=  'AP_IMPORT_VALIDATION_PKG.v_check_tax_info<-'
19658                                 ||P_calling_sequence;
19659 
19660   -------------------------------------------------------------------------
19661   debug_info := '(Check tax info 1) Check for control_amount';
19662   -------------------------------------------------------------------------
19663   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19664       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19665                                     debug_info);
19666   END IF;
19667 
19668   --Contract Payments: Modified the IF condition to add 'PREPAYMENT'.
19669 
19670   IF ( (p_invoice_rec.invoice_type_lookup_code IN ('STANDARD','PREPAYMENT') and
19671         NVL(p_invoice_rec.control_amount, 0) > NVL(p_invoice_rec.invoice_amount, 0)) OR
19672        (p_invoice_rec.invoice_type_lookup_code IN ('CREDIT', 'DEBIT') and -- bug 7299826
19673         NVL(abs(p_invoice_rec.control_amount), NVL(abs(p_invoice_rec.invoice_amount),0)) > NVL(abs(p_invoice_rec.invoice_amount),0))  --Bug 6925674 (Base bug6905106)
19674      ) THEN
19675 
19676     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
19677       (AP_IMPORT_INVOICES_PKG.g_invoices_table,
19678        p_invoice_rec.invoice_id,
19679        'INVALID CONTROL AMOUNT',
19680        p_default_last_updated_by,
19681        p_default_last_update_login,
19682        current_calling_sequence) <> TRUE) THEN
19683 
19684        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19685           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19686           'insert_rejections<-'||current_calling_sequence);
19687        END IF;
19688        RAISE check_tax_failure;
19689 
19690     END IF;
19691     l_current_invoice_status := 'N';
19692   END IF;
19693 
19694   -------------------------------------------------------------------------
19695   debug_info := '(Check tax info 2) Check for tax_related_invoice_id';
19696   -------------------------------------------------------------------------
19697   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19698       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19699                                     debug_info);
19700   END IF;
19701 
19702   IF ( p_invoice_rec.tax_related_invoice_id IS NOT NULL) THEN
19703 
19704     BEGIN
19705       SELECT invoice_id
19706         INTO l_related_inv_id
19707         FROM ap_invoices_all
19708        WHERE invoice_id = p_invoice_rec.tax_related_invoice_id
19709          AND vendor_id = p_invoice_rec.vendor_id
19710          AND vendor_site_id = p_invoice_rec.vendor_site_id
19711          AND cancelled_date IS NULL
19712          AND cancelled_by IS NULL;
19713 
19714     EXCEPTION
19715       WHEN no_data_found THEN
19716 
19717         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
19718           (AP_IMPORT_INVOICES_PKG.g_invoices_table,
19719            p_invoice_rec.invoice_id,
19720            'INVALID TAX RELATED INVOICE ID',
19721            p_default_last_updated_by,
19722            p_default_last_update_login,
19723            current_calling_sequence) <> TRUE) THEN
19724 
19725            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19726               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19727               'insert_rejections<-'||current_calling_sequence);
19728            END IF;
19729            RAISE check_tax_failure;
19730 
19731         END IF;
19732         l_current_invoice_status := 'N';
19733     END;
19734   END IF;  -- Validate only if tax_related_invoice_id is populated
19735 
19736   -------------------------------------------------------------------------
19737   debug_info := '(Check tax info 3) Check for calc_tax_during_import_flag';
19738   -------------------------------------------------------------------------
19739   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19740       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19741                                     debug_info);
19742   END IF;
19743 
19744   IF ( p_invoice_rec.calc_tax_during_import_flag = 'Y') THEN
19745 
19746     BEGIN
19747       SELECT invoice_id
19748         INTO l_exist_tax_line
19749         FROM ap_invoice_lines_interface
19750        WHERE invoice_id = p_invoice_rec.invoice_id
19751          AND line_type_lookup_code = 'TAX'
19752          AND ROWNUM =1;
19753 
19754     EXCEPTION
19755       WHEN no_data_found THEN
19756         NULL;
19757     END;
19758 
19759     IF (l_exist_tax_line IS NOT NULL) THEN
19760 
19761       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
19762         (AP_IMPORT_INVOICES_PKG.g_invoices_table,
19763          p_invoice_rec.invoice_id,
19764          'CANNOT CONTAIN TAX LINES',
19765          p_default_last_updated_by,
19766          p_default_last_update_login,
19767          current_calling_sequence) <> TRUE) THEN
19768           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19769             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19770             'insert_rejections<-'||current_calling_sequence);
19771          END IF;
19772          RAISE check_tax_failure;
19773        END IF;
19774       l_current_invoice_status := 'N';
19775 
19776     END IF;
19777   END IF;  -- Validate calc_tax_during_import_flag
19778 
19779   -------------------------------------------------------------------------
19780   debug_info := '(Check tax info 4) Validate if allocation structure is '||
19781                 'provided for inclusive lines when the invoice has more than '||
19782                 'one item line.';
19783   -------------------------------------------------------------------------
19784   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19785       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19786                                     debug_info);
19787   END IF;
19788 
19789   BEGIN
19790     SELECT 'Y'
19791       INTO l_alloc_not_provided
19792       FROM ap_invoices_interface aii
19793      WHERE aii.invoice_id = p_invoice_rec.invoice_id
19794        AND 1 < (SELECT COUNT(*)
19795                   FROM ap_invoice_lines_interface aili
19796                  WHERE aili.line_type_lookup_code <> 'TAX'
19797                    AND aili.invoice_id = aii.invoice_id)
19798        AND EXISTS (SELECT 'Y'
19799                     FROM ap_invoice_lines_interface ail2
19800                    WHERE ail2.invoice_id = aii.invoice_id
19801                      AND ail2.line_type_lookup_code = 'TAX'
19802                      AND ail2.line_group_number IS NULL
19803                      AND NVL(ail2.incl_in_taxable_line_flag, 'N') = 'Y');
19804   EXCEPTION
19805     WHEN NO_DATA_FOUND THEN
19806       l_alloc_not_provided := 'N';
19807 
19808   END;
19809 
19810   IF (l_alloc_not_provided = 'Y') THEN
19811     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
19812        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
19813        p_invoice_rec.invoice_id,
19814        'NO ALLOCATION RULES FOUND',
19815        p_default_last_updated_by,
19816        p_default_last_update_login,
19817        current_calling_sequence) <> TRUE) THEN
19818        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19819           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19820             'insert_rejections<-'||current_calling_sequence);
19821        END IF;
19822        RAISE check_tax_failure;
19823     END IF;
19824 
19825     l_current_invoice_status := 'N';
19826   END IF; -- end of validation if inclusive and alloc structure is not provided
19827 
19828   -------------------------------------------------------------------------
19829   debug_info := '(Check tax info 5) Check if any non-tax line has tax information';
19830   -------------------------------------------------------------------------
19831   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19832       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19833                                   debug_info);
19834   END IF;
19835 
19836   BEGIN
19837     SELECT 'Y'
19838       INTO l_tax_found_in_nontax_line
19839       FROM ap_invoices_interface aii
19840      WHERE aii.invoice_id = p_invoice_rec.invoice_id
19841        AND EXISTS (SELECT 'Y'
19842                      FROM ap_invoice_lines_interface ail2
19843                     WHERE ail2.invoice_id = aii.invoice_id
19844                       AND ail2.line_type_lookup_code <> 'TAX'
19845                       AND (ail2.tax_regime_code IS NOT NULL OR
19846                            ail2.tax IS NOT NULL OR
19847                            ail2.tax_jurisdiction_code IS NOT NULL OR
19848                            ail2.tax_status_code IS NOT NULL OR
19849                            ail2.tax_rate_id IS NOT NULL OR
19850                            ail2.tax_rate_code IS NOT NULL OR
19851                            ail2.tax_rate IS NOT NULL OR
19852                            ail2.incl_in_taxable_line_flag IS NOT NULL));
19853   EXCEPTION
19854     WHEN NO_DATA_FOUND THEN
19855       l_tax_found_in_nontax_line := 'N';
19856 
19857   END;
19858 
19859   IF (l_tax_found_in_nontax_line = 'Y') THEN
19860     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
19861        (AP_IMPORT_INVOICES_PKG.g_invoices_table,
19862        p_invoice_rec.invoice_id,
19863        'TAX DATA FOUND ON NONTAX LINES',
19864        p_default_last_updated_by,
19865        p_default_last_update_login,
19866        current_calling_sequence) <> TRUE) THEN
19867        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19868           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19869             'insert_rejections<-'||current_calling_sequence);
19870        END IF;
19871        RAISE check_tax_failure;
19872     END IF;
19873 
19874     l_current_invoice_status := 'N';
19875   END IF; -- end of validation if nont-tax lines have tax information
19876 
19877   -------------------------------------------------------------------------
19878   debug_info := '(Check tax info 6) Check if an invoice has a tax line '||
19879                 'matched to receipt and another allocated to item lines';
19880   -------------------------------------------------------------------------
19881   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19882       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19883                                   debug_info);
19884   END IF;
19885 
19886   -- Validation:  A tax-only invoice should not have a tax line matched to receipt and
19887   -- a tax line allocated to an item line
19888   -- This validation is only for tax-only invoices since if the invoice has a
19889   -- tax line matched to receipt in an invoice with item lines the rcv info is
19890   -- not taken into consideration.
19891   IF (NVL(p_invoice_rec.tax_only_flag, 'N') = 'Y') THEN
19892     BEGIN
19893       SELECT 'Y'
19894         INTO l_tax_lines_cannot_coexist
19895         FROM ap_invoices_interface aii
19896        WHERE aii.invoice_id = p_invoice_rec.invoice_id
19897          AND EXISTS (SELECT 'Y'
19898                        FROM ap_invoice_lines_interface ail2
19899                       WHERE ail2.invoice_id = aii.invoice_id
19900                         AND ail2.line_type_lookup_code = 'TAX'
19901                         AND ail2.rcv_transaction_id IS NOT NULL)
19902          AND EXISTS (SELECT 'Y'
19903                        FROM ap_invoice_lines_interface ail3
19904                       WHERE ail3.invoice_id = aii.invoice_id
19905                         AND ail3.line_type_lookup_code = 'TAX'
19906                         AND ail3.rcv_transaction_id IS NULL);
19907     EXCEPTION
19908       WHEN NO_DATA_FOUND THEN
19909         l_tax_lines_cannot_coexist := 'N';
19910 
19911     END;
19912 
19913     IF (l_tax_lines_cannot_coexist = 'Y') THEN
19914       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
19915          (AP_IMPORT_INVOICES_PKG.g_invoices_table,
19916          p_invoice_rec.invoice_id,
19917          'TAX LINE TYPES CANNOT COEXIST',
19918          p_default_last_updated_by,
19919          p_default_last_update_login,
19920          current_calling_sequence) <> TRUE) THEN
19921          IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19922             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19923               'insert_rejections<-'||current_calling_sequence);
19924          END IF;
19925          RAISE check_tax_failure;
19926       END IF;
19927 
19928       l_current_invoice_status := 'N';
19929     END IF; -- end of validation for tax lines matched to receipts and allocated
19930             -- to item lines
19931   END IF;  -- Is invoice tax-only?
19932 
19933   p_current_invoice_status := l_current_invoice_status;
19934 
19935   RETURN(TRUE);
19936 
19937 EXCEPTION
19938   WHEN OTHERS THEN
19939     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19940       AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19941                                     debug_info);
19942     END IF;
19943 
19944     IF (SQLCODE < 0) then
19945       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
19946         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
19947                                       SQLERRM);
19948       END IF;
19949     END IF;
19950     RETURN(FALSE);
19951 
19952 END v_check_tax_info;
19953 
19954 /*=============================================================================
19955  |  FUNCTION - V_Check_Tax_Line_Info()
19956  |
19957  |  DESCRIPTION
19958  |      This function will validate the following fields included in the
19959  |      ap_invoice_lines_interface table as part of the eTax Uptake project:
19960  |        control_amount
19961  |        assessable_value
19962  |        incl_in_taxable_line_flag
19963  |
19964  |      The other tax fields will be validated by the eTax API.  See DLD for
19965  |      details.
19966  |
19967  |  PARAMETERS
19968  |    p_invoice_rec - record for invoice header
19969  |    p_default_last_updated_by - default last updated by
19970  |    p_default_last_update_login - default last update login
19971  |    p_current_invoice_status - return the status of the invoice after the
19972  |                               validation
19973  |    P_calling_sequence -  Calling sequence
19974  |
19975  |  MODIFICATION HISTORY
19976  |    DATE          Author         Action
19977  |    20-JAN-2004   SYIDNER        Created
19978  |
19979  *============================================================================*/
19980   FUNCTION v_check_tax_line_info (
19981      p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
19982      p_default_last_updated_by      IN            NUMBER,
19983      p_default_last_update_login    IN            NUMBER,
19984      p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
19985      p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
19986 
19987   IS
19988 
19989     tax_line_info_failure      EXCEPTION;
19990     l_valid_info                VARCHAR2(1);
19991     l_current_invoice_status    VARCHAR2(1) := 'Y';
19992     current_calling_sequence    VARCHAR2(2000);
19993     debug_info                  VARCHAR2(500);
19994 
19995     --6412397
19996     l_po_line_location_id      ap_invoice_lines_interface.po_line_location_id%TYPE;
19997     l_location_id              zx_transaction_lines_gt.ship_from_location_id%type;
19998     l_ship_to_location_id      ap_supplier_sites_all.ship_to_location_id%type;
19999     l_bill_to_location_id      zx_transaction_lines_gt.bill_to_location_id%TYPE;
20000     l_fob_point                po_vendor_sites_all.fob_lookup_code%TYPE;
20001 
20002     l_dflt_tax_class_code      zx_transaction_lines_gt.input_tax_classification_code%type;
20003     l_allow_tax_code_override  varchar2(10);
20004     l_dummy                    number;
20005     -- Purchase Order Info
20006     l_ref_doc_application_id   zx_transaction_lines_gt.ref_doc_application_id%TYPE;
20007     l_ref_doc_entity_code      zx_transaction_lines_gt.ref_doc_entity_code%TYPE;
20008     l_ref_doc_event_class_code zx_transaction_lines_gt.ref_doc_event_class_code%TYPE;
20009     l_ref_doc_line_quantity    zx_transaction_lines_gt.ref_doc_line_quantity%TYPE;
20010     l_ref_doc_trx_level_type   zx_transaction_lines_gt.ref_doc_trx_level_type%TYPE;
20011     l_ref_doc_trx_id           zx_transaction_lines_gt.ref_doc_trx_id%TYPE;
20012     l_product_org_id           zx_transaction_lines_gt.product_org_id%TYPE;
20013 
20014     l_po_header_curr_conv_rate po_headers_all.rate%TYPE;
20015     l_uom_code                 mtl_units_of_measure.uom_code%TYPE;
20016 
20017     l_error_code               VARCHAR2(500);
20018     l_inv_hdr_org_id           ap_invoices_interface.org_id%TYPE;
20019     l_inv_hdr_vendor_id        ap_invoices_interface.vendor_id%TYPE;
20020     l_inv_hdr_vendor_site_id   ap_invoices_interface.vendor_site_id%TYPE;
20021     l_inv_hdr_inv_type         ap_invoices_interface.invoice_type_lookup_code%TYPE;
20022 
20023     l_event_class_code           zx_trx_headers_gt.event_class_code%TYPE;
20024     --6412397
20025 
20026   BEGIN
20027     -- Update the calling sequence
20028     --
20029     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_tax_line_info<-'
20030       ||P_calling_sequence;
20031 
20032 /* Bug 5206170: Removed the check for assessable value
20033     --------------------------------------------------------------------------
20034     debug_info := '(Check Tax Line Info 1) Check for Invalid sign in the '||
20035                   'assessable value';
20036     --------------------------------------------------------------------------
20037     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20038         AP_IMPORT_UTILITIES_PKG.Print(
20039         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20040     END IF;
20041 
20042     IF (NVL(p_invoice_lines_rec.assessable_value, 0) <> 0) THEN
20043       IF (SIGN(p_invoice_lines_rec.assessable_value) <>
20044           SIGN(p_invoice_lines_rec.amount)) THEN
20045         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20046           AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20047              p_invoice_lines_rec.invoice_line_id,
20048              'INVALID SIGN ASSESSABLE VALUE',
20049              p_default_last_updated_by,
20050              p_default_last_update_login,
20051              current_calling_sequence) <> TRUE) THEN
20052           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20053             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20054               'insert_rejections<-' ||current_calling_sequence);
20055           END IF;
20056           RAISE tax_line_info_failure;
20057         END IF;
20058 
20059         l_current_invoice_status := 'N';
20060 
20061       END IF;
20062     END IF;  -- end of validation for assessable value
20063 */
20064 
20065     --------------------------------------------------------------------------
20066     debug_info := '(Check Tax Line Info 2) Check for control_amount greater '||
20067                    'than line amount';
20068     --------------------------------------------------------------------------
20069     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20070         AP_IMPORT_UTILITIES_PKG.Print(
20071         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20072     END IF;
20073 
20074     IF (NVL(p_invoice_lines_rec.control_amount, 0) <> 0) THEN
20075 
20076       --Bug 6925674 (Base bug6905106) Starts
20077         BEGIN
20078 	        SELECT aii.invoice_type_lookup_code
20079 	        INTO   l_inv_hdr_inv_type
20080 	        FROM   ap_invoices_interface aii,
20081 	               ap_invoice_lines_interface aili
20082 	        WHERE  aii.invoice_id = aili.invoice_id
20083 	        AND    aili.ROWID = p_invoice_lines_rec.row_id;
20084 
20085             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20086                AP_IMPORT_UTILITIES_PKG.Print(
20087                AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20088             END IF;
20089         EXCEPTION
20090         WHEN OTHERS THEN
20091             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20092                AP_IMPORT_UTILITIES_PKG.Print(
20093                AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
20094             END IF;
20095         END;
20096 
20097         IF(l_inv_hdr_inv_type IN ('CREDIT', 'DEBIT') AND --Bug 7299826  Added DEBIT
20098           (abs(p_invoice_lines_rec.control_amount) >
20099            abs(p_invoice_lines_rec.amount))) THEN
20100 
20101            IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20102              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20103              p_invoice_lines_rec.invoice_line_id,
20104              'INVALID CONTROL AMOUNT ',
20105              p_default_last_updated_by,
20106              p_default_last_update_login,
20107              current_calling_sequence) <> TRUE) THEN
20108 
20109              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20110                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20111                  'insert_rejections<-' ||current_calling_sequence);
20112              END IF;
20113 
20114              RAISE tax_line_info_failure;
20115 
20116           END IF;
20117           l_current_invoice_status := 'N';
20118           --Bug 6925674 (Base bug6905106) Ends
20119         ELSIF (l_inv_hdr_inv_type NOT IN ('CREDIT', 'DEBIT') and    --bug 7299826
20120         (p_invoice_lines_rec.control_amount > p_invoice_lines_rec.amount)) THEN
20121           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20122              AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20123              p_invoice_lines_rec.invoice_line_id,
20124              'INVALID CONTROL AMOUNT ',
20125              p_default_last_updated_by,
20126              p_default_last_update_login,
20127              current_calling_sequence) <> TRUE) THEN
20128              IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20129                AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20130                'insert_rejections<-' ||current_calling_sequence);
20131              END IF;
20132 
20133 	     RAISE tax_line_info_failure;
20134           END IF;
20135 
20136           l_current_invoice_status := 'N';
20137 
20138         END IF;
20139     END IF;  -- end of validation for control amount
20140 
20141     --------------------------------------------------------------------------
20142     debug_info := '(Check Tax Line Info 3) Tax should not be inclusive if '||
20143                   'tax line is PO matched';
20144     --------------------------------------------------------------------------
20145     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20146         AP_IMPORT_UTILITIES_PKG.Print(
20147         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20148     END IF;
20149 
20150     IF (p_invoice_lines_rec.line_type_lookup_code = 'TAX'
20151         AND NVL(p_invoice_lines_rec.incl_in_taxable_line_flag, 'N') = 'Y'
20152         AND (p_invoice_lines_rec.po_header_id IS NOT NULL OR
20153              p_invoice_lines_rec.po_number IS NOT NULL OR
20154              p_invoice_lines_rec.po_line_id IS NOT NULL OR
20155              p_invoice_lines_rec.po_line_number IS NOT NULL OR
20156              p_invoice_lines_rec.po_line_location_id IS NOT NULL OR
20157              p_invoice_lines_rec.po_shipment_num IS NOT NULL OR
20158              p_invoice_lines_rec.po_distribution_id IS NOT NULL OR
20159              p_invoice_lines_rec.po_distribution_num IS NOT NULL)) THEN
20160 
20161       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20162        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20163           p_invoice_lines_rec.invoice_line_id,
20164            'TAX CANNOT BE INCLUDED',
20165            p_default_last_updated_by,
20166            p_default_last_update_login,
20167            current_calling_sequence) <> TRUE) THEN
20168         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20169           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20170             'insert_rejections<-' ||current_calling_sequence);
20171         END IF;
20172         RAISE tax_line_info_failure;
20173       END IF;
20174 
20175       l_current_invoice_status := 'N';
20176 
20177     END IF;  -- end of validation for incl_in_taxable_line_flag
20178 
20179     --Bug 6412397
20180     --------------------------------------------------------------------------
20181     debug_info := '(Check Tax Line Info 4) Tax_regime_code and tax are '||
20182                   'required in tax lines to be imported';
20183     --------------------------------------------------------------------------
20184     IF (p_invoice_lines_rec.line_type_lookup_code = 'TAX' AND
20185         p_invoice_lines_rec.tax_classification_code IS NULL AND
20186         p_invoice_lines_rec.tax_rate_code IS NULL) THEN
20187 
20188     --
20189     --  Fetch header vendor_id, vendor_site_id, invoice type
20190     --
20191 
20192     BEGIN
20193         SELECT NVL(p_invoice_lines_rec.org_id, aii.org_id),
20194                aii.vendor_id,
20195                aii.vendor_site_id,
20196                aii.invoice_type_lookup_code
20197         INTO   l_inv_hdr_org_id,
20198                l_inv_hdr_vendor_id,
20199                l_inv_hdr_vendor_site_id,
20200                l_inv_hdr_inv_type
20201         FROM   ap_invoices_interface aii,
20202                ap_invoice_lines_interface aili
20203         WHERE  aii.invoice_id = aili.invoice_id
20204         AND    aili.ROWID = p_invoice_lines_rec.row_id;
20205 
20206         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20207             AP_IMPORT_UTILITIES_PKG.Print(
20208             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20209         END IF;
20210     EXCEPTION
20211     WHEN OTHERS THEN
20212         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20213           AP_IMPORT_UTILITIES_PKG.Print(
20214             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
20215         END IF;
20216     END;
20217     ----------------------------------------------------------------------
20218     debug_info := 'Step 4.1: Get location_id for vendor site';
20219     ----------------------------------------------------------------------
20220         BEGIN
20221           SELECT location_id,   ship_to_location_id,   fob_lookup_code
20222             INTO l_location_id, l_ship_to_location_id, l_fob_point
20223             FROM ap_supplier_sites_all
20224            WHERE vendor_site_id = l_inv_hdr_vendor_site_id;
20225 
20226         EXCEPTION
20227           WHEN no_data_found THEN
20228             l_location_id           := null;
20229             l_ship_to_location_id   := null;
20230             l_fob_point            := null;
20231         END;
20232     ----------------------------------------------------------------------
20233     debug_info := 'Step 4.2: Get location_id for org_id';
20234     ----------------------------------------------------------------------
20235         BEGIN
20236           SELECT location_id
20237             INTO l_bill_to_location_id
20238             FROM hr_all_organization_units
20239            WHERE organization_id = l_inv_hdr_org_id;
20240 
20241         EXCEPTION
20242           WHEN no_data_found THEN
20243              l_bill_to_location_id := null;
20244         END;
20245 
20246     -------------------------------------------------------------------
20247     debug_info := 'Step 4.5: Get Additional PO matched  info ';
20248     -------------------------------------------------------------------
20249         IF ( p_invoice_lines_rec.po_line_location_id IS NOT NULL) THEN
20250 
20251           -- this assignment is required since the p_po_line_location_id
20252           -- parameter is IN/OUT.  However, in this case it will not be
20253           -- modified because the po_distribution_id is not provided
20254 
20255         l_po_line_location_id := p_invoice_lines_rec.po_line_location_id;
20256 
20257         IF NOT (AP_ETAX_UTILITY_PKG.Get_PO_Info(
20258            P_Po_Line_Location_Id         => l_po_line_location_id,
20259            P_PO_Distribution_Id          => null,
20260            P_Application_Id              => l_ref_doc_application_id,
20261            P_Entity_code                 => l_ref_doc_entity_code,
20262            P_Event_Class_Code            => l_ref_doc_event_class_code,
20263            P_PO_Quantity                 => l_ref_doc_line_quantity,
20264            P_Product_Org_Id              => l_product_org_id,
20265            P_Po_Header_Id                => l_ref_doc_trx_id,
20266            P_Po_Header_curr_conv_rate    => l_po_header_curr_conv_rate,
20267            P_Uom_Code                   => l_uom_code,
20268            P_Dist_Qty                    => l_dummy,
20269            P_Ship_Price                  => l_dummy,
20270            P_Error_Code                  => l_error_code,
20271            P_Calling_Sequence            => current_calling_sequence)) THEN
20272 
20273            debug_info := 'Step 4.5: Get Additional PO matched info failed: '||
20274 l_error_code;
20275         END IF;
20276 
20277         l_ref_doc_trx_level_type := 'SHIPMENT';
20278 
20279         ELSE
20280          l_ref_doc_application_id     := Null;
20281          l_ref_doc_entity_code        := Null;
20282          l_ref_doc_event_class_code   := Null;
20283          l_ref_doc_line_quantity      := Null;
20284          l_product_org_id             := Null;
20285          l_ref_doc_trx_id             := Null;
20286          l_ref_doc_trx_level_type     := Null;
20287         END IF;
20288 
20289     -------------------------------------------------------------------
20290     debug_info := 'Step 4.6: Get event class code';
20291     -------------------------------------------------------------------
20292 
20293         IF NOT(AP_ETAX_UTILITY_PKG.Get_Event_Class_Code(
20294           P_Invoice_Type_Lookup_Code => l_inv_hdr_inv_type,
20295           P_Event_Class_Code         => l_event_class_code,
20296           P_error_code               => l_error_code,
20297           P_calling_sequence         => current_calling_sequence)) THEN
20298 
20299           debug_info := 'Step 4.6: Get event class code failed: '||
20300 l_error_code;
20301 
20302         END IF;
20303 
20304     -------------------------------------------------------------------
20305     debug_info := 'Step 4.7: Call tax classification code defaulting api';
20306     -------------------------------------------------------------------
20307 
20308         ZX_AP_TAX_CLASSIFICATN_DEF_PKG.get_default_tax_classification
20309         (p_ref_doc_application_id           => l_ref_doc_application_id,
20310          p_ref_doc_entity_code              => l_ref_doc_entity_code,
20311          p_ref_doc_event_class_code         => l_ref_doc_event_class_code,
20312          p_ref_doc_trx_id                   => l_ref_doc_trx_id,
20313          p_ref_doc_line_id                  =>
20314 p_invoice_lines_rec.po_line_location_id,
20315          p_ref_doc_trx_level_type           => l_ref_doc_trx_level_type,
20316 --'SHIPMENT',
20317          p_vendor_id                        => l_inv_hdr_vendor_id,
20318          p_vendor_site_id                   => l_inv_hdr_vendor_site_id,
20319          p_code_combination_id              =>
20320 p_invoice_lines_rec.default_dist_ccid,
20321          p_concatenated_segments            => null,
20322          p_templ_tax_classification_cd      => null,
20323          p_ship_to_location_id              =>
20324 nvl(p_invoice_lines_rec.ship_to_location_id,
20325                                                    l_ship_to_location_id),
20326          p_ship_to_loc_org_id               => null,
20327          p_inventory_item_id                =>
20328 p_invoice_lines_rec.inventory_item_id,
20329          p_item_org_id                      => l_product_org_id,
20330          p_tax_classification_code          => l_dflt_tax_class_code,
20331          p_allow_tax_code_override_flag     => l_allow_tax_code_override,
20332          APPL_SHORT_NAME                    => 'SQLAP',
20333          FUNC_SHORT_NAME                    => 'NONE',
20334          p_calling_sequence                 => current_calling_sequence,
20335 --'AP_ETAX_SERVICES_PKG',
20336          p_event_class_code                 => NULL, --p_event_class_code,
20337          p_entity_code                      => 'AP_INVOICES',
20338          p_application_id                   => 200,
20339          p_internal_organization_id         => l_inv_hdr_org_id );
20340 
20341 
20342          p_invoice_lines_rec.tax_classification_code := l_dflt_tax_class_code;
20343     END IF;
20344     -- After validation check again
20345     -- End Bug 6412397
20346 
20347     --------------------------------------------------------------------------
20348     debug_info := '(Check Tax Line Info 4.8) Tax_regime_code and tax are '||
20349                   'required in tax lines to be imported'; -- Bug 6412397
20350     --------------------------------------------------------------------------
20351     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20352         AP_IMPORT_UTILITIES_PKG.Print(
20353         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20354     END IF;
20355 
20356     IF (p_invoice_lines_rec.line_type_lookup_code = 'TAX' AND
20357         p_invoice_lines_rec.tax_classification_code is null --6255826
20358           and p_invoice_lines_rec.TAX_RATE_CODE is null   --6255826
20359         )  THEN
20360 
20361       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20362        AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20363           p_invoice_lines_rec.invoice_line_id,
20364            'INSUFFICIENT TAX INFO', --bug6255826 Replaced TAX INFO REQUIRED
20365            p_default_last_updated_by,
20366            p_default_last_update_login,
20367            current_calling_sequence) <> TRUE) THEN
20368         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20369           AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20370             'insert_rejections<-' ||current_calling_sequence);
20371         END IF;
20372         RAISE tax_line_info_failure;
20373       END IF;
20374 
20375       l_current_invoice_status := 'N';
20376 
20377     END IF;  -- end of validation tax_Regime_code and tax column in tax lines
20378 
20379   p_current_invoice_status := l_current_invoice_status;
20380   RETURN (TRUE);
20381 
20382   EXCEPTION
20383     WHEN OTHERS THEN
20384       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20385         AP_IMPORT_UTILITIES_PKG.Print(
20386           AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20387       END IF;
20388 
20389       IF (SQLCODE < 0) THEN
20390         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20391           AP_IMPORT_UTILITIES_PKG.Print(
20392             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
20393         END IF;
20394       END IF;
20395       RETURN(FALSE);
20396 
20397   END v_check_tax_line_info;
20398 
20399 
20400  FUNCTION v_check_line_purch_category(
20401 	p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20402         p_default_last_updated_by      IN            NUMBER,
20403         p_default_last_update_login    IN            NUMBER,
20404         p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
20405         p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
20406 
20407   IS
20408     purch_category_check_failure EXCEPTION;
20409     l_purchasing_category_id	AP_INVOICE_LINES_ALL.PURCHASING_CATEGORY_ID%TYPE;
20410     l_current_invoice_status    VARCHAR2(1) := 'Y';
20411     current_calling_sequence    VARCHAR2(2000);
20412     debug_info                  VARCHAR2(500);
20413 
20414   BEGIN
20415 
20416     -- Update the calling sequence
20417     --
20418     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_purch_category<-'
20419       ||P_calling_sequence;
20420 
20421     --------------------------------------------------------------------------
20422     debug_info := '(Check Line Purchasing_Category Info 1) If purchasing_category_id and '||
20423 		   'concatenated segments are provided'||
20424 		   ' then cross validate the info from concatenated segments';
20425     --------------------------------------------------------------------------
20426     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20427         AP_IMPORT_UTILITIES_PKG.Print(
20428         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20429     END IF;
20430 
20431     -- Bug 5448579
20432     IF AP_IMPORT_INVOICES_PKG.g_structure_id IS NULL THEN
20433       p_invoice_lines_rec.purchasing_category_id := NULL;
20434       p_invoice_lines_rec.purchasing_category := NULL;
20435     END IF;
20436 
20437     IF (p_invoice_lines_rec.line_type_lookup_code <> 'ITEM') THEN
20438 
20439           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20440                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20441                p_invoice_lines_rec.invoice_line_id,
20442                'INCONSISTENT CATEGORY',
20443                p_default_last_updated_by,
20444                p_default_last_update_login,
20445                current_calling_sequence,
20446                'Y',
20447                'INVOICE LINE NUMBER',
20448                p_invoice_lines_rec.line_number) <> TRUE) THEN
20449 
20450                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20451                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20452                 'insert_rejections<-'||current_calling_sequence);
20453                END IF;
20454 
20455                RAISE purch_category_check_failure;
20456 
20457           END IF;
20458 
20459           l_current_invoice_status := 'N';
20460 
20461     END IF;
20462 
20463     IF (p_invoice_lines_rec.purchasing_category_id IS NOT NULL AND
20464         p_invoice_lines_rec.purchasing_category IS NOT NULL) THEN
20465 
20466           l_purchasing_category_id := FND_FLEX_EXT.GET_CCID('INV', 'MCAT',
20467            AP_IMPORT_INVOICES_PKG.g_structure_id,
20468            to_char(sysdate,'YYYY/MM/DD HH24:MI:SS'),p_invoice_lines_rec.purchasing_category);
20469 
20470           IF (l_purchasing_category_id <> p_invoice_lines_rec.purchasing_category_id) THEN
20471 
20472 	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20473                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20474                p_invoice_lines_rec.invoice_line_id,
20475                'INCONSISTENT CATEGORY',
20476                p_default_last_updated_by,
20477                p_default_last_update_login,
20478                current_calling_sequence,
20479                'Y',
20480                'INVOICE LINE NUMBER',
20481                p_invoice_lines_rec.line_number) <> TRUE) THEN
20482 
20483                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20484                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20485                 'insert_rejections<-'||current_calling_sequence);
20486                END IF;
20487 
20488                RAISE purch_category_check_failure;
20489 
20490              END IF;
20491 
20492              l_current_invoice_status := 'N';
20493 
20494           END IF;
20495 
20496     ELSIF (p_invoice_lines_rec.purchasing_category IS NOT NULL) THEN
20497 
20498        --------------------------------------------------------------------------
20499        debug_info := '(Check Line purchasing_Category Info 2) If just concatenated segments'||
20500 		     'are provided then derive the purchasing_category_id from that info';
20501        --------------------------------------------------------------------------
20502        IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20503          AP_IMPORT_UTILITIES_PKG.Print(
20504          AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20505        END IF;
20506 
20507        l_purchasing_category_id := FND_FLEX_EXT.GET_CCID('INV', 'MCAT',
20508           AP_IMPORT_INVOICES_PKG.g_structure_id,
20509           to_char(sysdate,'YYYY/MM/DD HH24:MI:SS'),p_invoice_lines_rec.purchasing_category);
20510 
20511        IF ((l_purchasing_category_id is not null) and (l_purchasing_category_id <> 0 )) THEN
20512           p_invoice_lines_rec.purchasing_category_id := l_purchasing_category_id;
20513 
20514        ELSE
20515 
20516           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20517                AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20518                p_invoice_lines_rec.invoice_line_id,
20519                'INVALID CATEGORY',
20520                p_default_last_updated_by,
20521                p_default_last_update_login,
20522                current_calling_sequence,
20523                'Y',
20524                'INVOICE LINE NUMBER',
20525                p_invoice_lines_rec.line_number) <> TRUE) THEN
20526 
20527                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20528                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20529                 'insert_rejections<-'||current_calling_sequence);
20530                END IF;
20531 
20532                RAISE purch_category_check_failure;
20533 
20534              END IF;
20535 
20536              l_current_invoice_status := 'N';
20537 
20538        END IF;
20539 
20540     END IF;
20541 
20542     --------------------------------------------------------
20543       -- Validate Item Category Information
20544       -- If both Purchasing_Category and PO Information is provided
20545       -- then validate the Purchasing_Category info provided in interface
20546       -- against the one on the PO_Line.
20547     --------------------------------------------------------
20548     IF (l_current_invoice_status = 'Y' AND
20549 	 p_invoice_lines_rec.purchasing_category_id IS NOT NULL AND
20550           (p_invoice_lines_rec.po_line_id is not null or
20551 	   p_invoice_lines_rec.po_line_location_id is not null)) THEN
20552 
20553        BEGIN
20554 
20555 	  IF (p_invoice_lines_rec.po_line_id IS NOT NULL) THEN
20556    	     SELECT category_id
20557 	     INTO l_purchasing_category_id
20558 	     FROM po_lines_all
20559 	     WHERE po_line_id = p_invoice_lines_rec.po_line_id;
20560 
20561 	  ELSE
20562 	     SELECT pl.category_id
20563 	     INTO l_purchasing_category_id
20564 	     FROM po_lines_all pl, po_line_locations_all pll
20565 	     WHERE pll.line_location_id = p_invoice_lines_rec.po_line_location_id
20566 	     AND pl.po_line_id = pll.po_line_id;
20567 
20568 	  END IF;
20569 
20570 	  IF (l_purchasing_category_id <> p_invoice_lines_rec.purchasing_category_id) THEN
20571 
20572              IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20573                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20574                  p_invoice_lines_rec.invoice_line_id,
20575                  'INCONSISTENT CATEGORY',
20576                  p_default_last_updated_by,
20577                  p_default_last_update_login,
20578                  current_calling_sequence,
20579                  'Y',
20580                  'INVOICE LINE NUMBER',
20581                  p_invoice_lines_rec.line_number) <> TRUE) THEN
20582 
20583                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20584                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20585                 'insert_rejections<-'||current_calling_sequence);
20586                END IF;
20587 
20588                RAISE purch_category_check_failure;
20589 
20590              END IF;
20591 
20592              l_current_invoice_status := 'N';
20593 
20594           /* if the information provided and the information on the PO Line is the same
20595 	   then we do not REJECT, but ignore the value provided by the user, since we will
20596 	   not be denormalizing the purchasing category info of the PO Line onto the
20597 	   invoice lines for matched cases */
20598 
20599           ELSE
20600 
20601 	     p_invoice_lines_rec.purchasing_category_id := NULL;
20602 
20603           END IF;
20604 
20605         END;
20606 
20607      END IF;
20608 
20609      p_current_invoice_status := l_current_invoice_status;
20610 
20611      RETURN (TRUE);
20612 
20613  END v_check_line_purch_category;
20614 
20615 
20616  FUNCTION v_check_line_cost_factor(
20617 	p_invoice_lines_rec   IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20618         p_default_last_updated_by      IN            NUMBER,
20619         p_default_last_update_login    IN            NUMBER,
20620         p_current_invoice_status       IN OUT NOCOPY VARCHAR2,
20621         p_calling_sequence             IN            VARCHAR2) RETURN BOOLEAN
20622 
20623   IS
20624     cost_factor_check_failure EXCEPTION;
20625     l_cost_factor_id	AP_INVOICE_LINES_ALL.COST_FACTOR_ID%TYPE;
20626     l_valid_cost_factor VARCHAR2(1);
20627     l_current_invoice_status    VARCHAR2(1) := 'Y';
20628     current_calling_sequence    VARCHAR2(2000);
20629     debug_info                  VARCHAR2(500);
20630 
20631   BEGIN
20632     -- Update the calling sequence
20633     --
20634     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_cost_factor<-'
20635       ||P_calling_sequence;
20636 
20637     --------------------------------------------------------------------------
20638     debug_info := '(Check Line Cost_Factor Info 1) If cost_factor_id and '||
20639 		   'cost_factor_name provided'||
20640 		   ' then cross validate the info';
20641     --------------------------------------------------------------------------
20642     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20643         AP_IMPORT_UTILITIES_PKG.Print(
20644         AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20645     END IF;
20646 
20647     IF (p_invoice_lines_rec.line_type_lookup_code IN ('TAX','FREIGHT','MISCELLANEOUS')) THEN
20648 
20649       IF (p_invoice_lines_rec.cost_factor_name IS NOT NULL) THEN
20650  	debug_info := '(Check Line Cost_Factor Info 2) Check if cost_factor_name is provided'
20651 		   ||' then derive cost_factor_id';
20652         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20653            AP_IMPORT_UTILITIES_PKG.Print(
20654            AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20655         END IF;
20656 
20657         BEGIN
20658 
20659    	  SELECT price_element_type_id
20660 	  INTO l_cost_factor_id
20661 	  FROM pon_price_element_types_vl
20662 	  WHERE name = p_invoice_lines_rec.cost_factor_name;
20663 
20664     	  EXCEPTION WHEN OTHERS THEN
20665 
20666   	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20667                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20668                  p_invoice_lines_rec.invoice_line_id,
20669                  'INVALID COST FACTOR INFO',
20670                  p_default_last_updated_by,
20671                  p_default_last_update_login,
20672                  current_calling_sequence,
20673                  'Y',
20674                  'INVOICE LINE NUMBER',
20675                  p_invoice_lines_rec.line_number) <> TRUE) THEN
20676 
20677                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20678                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20679                 'insert_rejections<-'||current_calling_sequence);
20680                END IF;
20681 
20682                RAISE cost_factor_check_failure;
20683 
20684              END IF;
20685 
20686              l_current_invoice_status := 'N';
20687         END;
20688 
20689       END IF;  /* IF p_invoice_lines_rec.cost_factor_name IS NOT NULL */
20690 
20691 
20692       IF (l_current_invoice_status = 'Y') THEN
20693 
20694         IF (p_invoice_lines_rec.cost_factor_id IS NOT NULL and
20695 	  p_invoice_lines_rec.cost_factor_name IS NOT NULL) THEN
20696 
20697  	  debug_info := '(Check Line Cost_Factor Info 2) Cross validate '||
20698 			'cost_factor_name and cost_factor_id information';
20699           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20700              AP_IMPORT_UTILITIES_PKG.Print(
20701              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20702           END IF;
20703 
20704 	  IF (l_cost_factor_id <> p_invoice_lines_rec.cost_factor_id) THEN
20705 
20706     	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20707                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20708                  p_invoice_lines_rec.invoice_line_id,
20709                  'INVALID COST FACTOR INFO',
20710                  p_default_last_updated_by,
20711                  p_default_last_update_login,
20712                  current_calling_sequence,
20713                  'Y',
20714                  'INVOICE LINE NUMBER',
20715                  p_invoice_lines_rec.line_number) <> TRUE) THEN
20716 
20717                 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20718                   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20719                  'insert_rejections<-'||current_calling_sequence);
20720                 END IF;
20721 
20722                 RAISE cost_factor_check_failure;
20723 
20724               END IF;
20725 
20726               l_current_invoice_status := 'N';
20727 
20728   	   END IF;
20729 
20730          ELSIF (p_invoice_lines_rec.cost_factor_id IS NULL) THEN
20731 
20732   	   debug_info := '(Check Line Cost_Factor Info 4) If cost_factor_id is null and '||
20733 		   'cost_factor_name is provided, then assign the derived cost_factor_id'
20734 		   ||' then derive cost_factor_id';
20735            IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20736              AP_IMPORT_UTILITIES_PKG.Print(
20737              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20738            END IF;
20739 
20740            p_invoice_lines_rec.cost_factor_id := l_cost_factor_id;
20741 
20742          ELSIF (p_invoice_lines_rec.cost_factor_id IS NOT NULL) THEN
20743 
20744 	   debug_info := '(Check Line Cost Factor Info 5) If cost_factor_id is'||
20745 	   		' not null , then validate it against the valid set of'||
20746 			' cost factors';
20747 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20748              AP_IMPORT_UTILITIES_PKG.Print(
20749              AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20750            END IF;
20751 
20752            BEGIN
20753 	      SELECT 'Y'
20754 	      INTO l_valid_cost_factor
20755 	      FROM pon_price_element_types_vl
20756 	      WHERE price_element_type_id = p_invoice_lines_rec.cost_factor_id;
20757 
20758       	    EXCEPTION WHEN OTHERS THEN
20759 
20760   	     IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20761                  AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20762                  p_invoice_lines_rec.invoice_line_id,
20763                  'INVALID COST FACTOR INFO',
20764                  p_default_last_updated_by,
20765                  p_default_last_update_login,
20766                  current_calling_sequence,
20767                  'Y',
20768                  'INVOICE LINE NUMBER',
20769                  p_invoice_lines_rec.line_number) <> TRUE) THEN
20770 
20771                IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20772                  AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20773                 'insert_rejections<-'||current_calling_sequence);
20774                END IF;
20775 
20776                RAISE cost_factor_check_failure;
20777 
20778              END IF;
20779 
20780              l_current_invoice_status := 'N';
20781 
20782            END;
20783 
20784          END IF;
20785 
20786       END IF; /* l_current_invoice_status = 'Y' */
20787 
20788     --if cost_factor information is provided on non-charge lines, then do not
20789     --perform any validation, just ignore the value in this fields, and make sure
20790     --to not insert the values onto the non-charge lines.
20791     ELSE
20792 
20793       p_invoice_lines_rec.cost_factor_id := NULL;
20794       p_invoice_lines_rec.cost_factor_name := NULL;
20795 
20796     END IF ;  /* IF p_invoice_lines_rec.line_type_lookup_code ... */
20797 
20798     p_current_invoice_status := l_current_invoice_status;
20799 
20800     RETURN (TRUE);
20801 
20802   END v_check_line_cost_factor;
20803 
20804   FUNCTION v_check_line_retainage(
20805         p_invoice_lines_rec		IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
20806 	p_retainage_ccid		IN            NUMBER,
20807 	p_default_last_updated_by	IN            NUMBER,
20808 	p_default_last_update_login	IN            NUMBER,
20809 	p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
20810 	p_calling_sequence		IN            VARCHAR2) RETURN BOOLEAN IS
20811 
20812 	l_ret_status          Varchar2(100);
20813 	l_msg_data            Varchar2(4000);
20814 
20815 	l_retained_amount     Number;
20816 
20817 	retainage_check_failure     EXCEPTION;
20818 	l_current_invoice_status    VARCHAR2(1) := 'Y';
20819 	current_calling_sequence    VARCHAR2(2000);
20820 	debug_info                  VARCHAR2(500);
20821 
20822   Begin
20823 	-- Update the calling sequence
20824 	--
20825 	current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_line_retainage<-'
20826 					||P_calling_sequence;
20827 
20828 	--------------------------------------------------------------------------
20829 	debug_info := '(Check Retainage 1) Get retained amount based on po shipment and line amount';
20830 	--------------------------------------------------------------------------
20831 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20832             AP_IMPORT_UTILITIES_PKG.Print(
20833             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20834         END IF;
20835 
20836 	l_retained_amount := ap_invoice_lines_utility_pkg.get_retained_amount
20837 					(p_invoice_lines_rec.po_line_location_id,
20838 					 p_invoice_lines_rec.amount);
20839 
20840 	--------------------------------------------------------------------------
20841 	debug_info := '(Check Retainage 2) Check for retainage account';
20842 	--------------------------------------------------------------------------
20843 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20844             AP_IMPORT_UTILITIES_PKG.Print(
20845             AP_IMPORT_INVOICES_PKG.g_debug_switch, debug_info);
20846         END IF;
20847 
20848 	If l_retained_amount IS NOT NULL Then
20849 
20850 	   If p_retainage_ccid IS NULL Then
20851 
20852 		If (AP_IMPORT_UTILITIES_PKG.insert_rejections(
20853 				AP_IMPORT_INVOICES_PKG.g_invoice_lines_table,
20854 				p_invoice_lines_rec.invoice_line_id,
20855 				'RETAINAGE ACCT REQD',
20856 				p_default_last_updated_by,
20857 				p_default_last_update_login,
20858 				current_calling_sequence,
20859 				'Y',
20860 				'INVOICE LINE NUMBER',
20861 				p_invoice_lines_rec.line_number) <> TRUE) Then
20862 
20863 			If (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') Then
20864 			    AP_IMPORT_UTILITIES_PKG.Print
20865 				(AP_IMPORT_INVOICES_PKG.g_debug_switch, 'insert_rejections<-'||current_calling_sequence);
20866 			End If;
20867 
20868 			RAISE retainage_check_failure;
20869 		End If;
20870 
20871                 l_current_invoice_status := 'N';
20872 	   Else
20873 
20874 		p_invoice_lines_rec.retained_amount := l_retained_amount;
20875 
20876 	   End If;
20877 	End If;
20878 
20879 	p_current_invoice_status := l_current_invoice_status;
20880 	RETURN (TRUE);
20881 
20882   EXCEPTION
20883 	WHEN OTHERS THEN
20884 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20885 			AP_IMPORT_UTILITIES_PKG.Print(
20886 				AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
20887 		END IF;
20888 
20889 		IF (SQLCODE < 0) THEN
20890 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
20891 				AP_IMPORT_UTILITIES_PKG.Print(
20892 					AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
20893 			END IF;
20894 		END IF;
20895 		RETURN(FALSE);
20896 
20897   End v_check_line_retainage;
20898 
20899 
20900 
20901 
20902   FUNCTION v_check_payment_defaults(
20903     p_invoice_rec               IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
20904     p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
20905     p_calling_sequence          IN            VARCHAR2,
20906     p_default_last_updated_by   IN            NUMBER,
20907     p_default_last_update_login IN            NUMBER) return boolean is
20908 
20909 
20910   debug_info                  VARCHAR2(500);
20911   l_current_invoice_status    VARCHAR2(1) := 'Y';
20912   current_calling_sequence    VARCHAR2(2000);
20913   l_dummy                     varchar2(1);
20914   pmt_attr_validation_failure exception;
20915   l_IBY_PAYMENT_METHOD        varchar2(80);
20916   l_PAYMENT_REASON            varchar2(80);
20917   l_BANK_CHARGE_BEARER_DSP    varchar2(80);
20918   l_DELIVERY_CHANNEL          varchar2(80);
20919   l_SETTLEMENT_PRIORITY_DSP   varchar2(80);
20920   l_bank_account_num          varchar2(100);
20921   l_bank_account_name         varchar2(80);
20922   l_bank_branch_name          varchar2(360);
20923   l_bank_branch_num           varchar2(30);
20924   l_bank_name                 varchar2(360);
20925   l_bank_number               varchar2(30);
20926 
20927 
20928 
20929 
20930   l_PAYMENT_METHOD_CODE       varchar2(30);
20931   l_PAYMENT_REASON_CODE       varchar2(30);
20932   l_BANK_CHARGE_BEARER        varchar2(30);
20933   l_DELIVERY_CHANNEL_CODE     varchar2(30);
20934   l_SETTLEMENT_PRIORITY       varchar2(30);
20935   l_PAY_ALONE                 varchar2(30);
20936   l_external_bank_account_id  number;
20937   l_exclusive_payment_flag    varchar2(1);
20938   l_payment_reason_comments   varchar2(240); --4874927
20939   -- Bug 5448579
20940   l_valid_payment_method      IBY_PAYMENT_METHODS_VL.Payment_Method_Code%TYPE;
20941 
20942   --Bug 8213679
20943   l_remit_party_id	AP_INVOICES_ALL.PARTY_ID%TYPE;
20944   l_remit_party_site_id	AP_INVOICES_ALL.PARTY_SITE_ID%TYPE;
20945   --Bug 8213679
20946 
20947 
20948   begin
20949 
20950 
20951     current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_payment_defaults<-'
20952 					||P_calling_sequence;
20953 
20954     debug_info := 'Check the payment reason';
20955 
20956     if p_invoice_rec.payment_reason_code is not null then
20957 
20958       begin
20959         select 'x'
20960         into l_dummy
20961         from iby_payment_reasons_vl
20962         where payment_reason_code = p_invoice_rec.payment_reason_code
20963         and rownum = 1;
20964 
20965       exception
20966         when no_data_found then
20967           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
20968                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
20969                 p_invoice_rec.invoice_id,
20970                 'INVALID PAYMENT REASON',
20971                 p_default_last_updated_by,
20972                 p_default_last_update_login,
20973                 current_calling_sequence) <> TRUE) THEN
20974             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
20975               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
20976                                             'insert_rejections<-'
20977                                             ||current_calling_sequence);
20978             END IF;
20979             RAISE pmt_attr_validation_failure;
20980           END IF;
20981 
20982           l_current_invoice_status := 'N';
20983 
20984        end;
20985     end if;
20986 
20987 
20988 
20989     debug_info := 'Check the bank charge bearer';
20990 
20991     if p_invoice_rec.bank_charge_bearer is not null then
20992 
20993       begin
20994         select 'x'
20995         into l_dummy
20996         from fnd_lookups
20997         where lookup_type = 'IBY_BANK_CHARGE_BEARER'
20998         and lookup_code = p_invoice_rec.bank_charge_bearer
20999         and rownum = 1;
21000 
21001       exception
21002         when no_data_found then
21003           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21004                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21005                 p_invoice_rec.invoice_id,
21006                 'INVALID BANK CHARGE BEARER',
21007                 p_default_last_updated_by,
21008                 p_default_last_update_login,
21009                 current_calling_sequence) <> TRUE) THEN
21010             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21011               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21012                                             'insert_rejections<-'
21013                                             ||current_calling_sequence);
21014             END IF;
21015             RAISE pmt_attr_validation_failure;
21016           END IF;
21017 
21018           l_current_invoice_status := 'N';
21019 
21020        end;
21021     end if;
21022 
21023 
21024 
21025     debug_info := 'Check the delivery channel code';
21026 
21027     if p_invoice_rec.delivery_channel_code is not null then
21028 
21029       begin
21030         select 'x'
21031         into l_dummy
21032         from iby_delivery_channels_vl
21033         where delivery_channel_code = p_invoice_rec.delivery_channel_code
21034         and rownum = 1;
21035 
21036       exception
21037         when no_data_found then
21038           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21039                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21040                 p_invoice_rec.invoice_id,
21041                 'INVALID DELIVERY CHANNEL CODE',
21042                 p_default_last_updated_by,
21043                 p_default_last_update_login,
21044                 current_calling_sequence) <> TRUE) THEN
21045             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21046               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21047                                             'insert_rejections<-'
21048                                             ||current_calling_sequence);
21049             END IF;
21050             RAISE pmt_attr_validation_failure;
21051           END IF;
21052 
21053           l_current_invoice_status := 'N';
21054 
21055        end;
21056     end if;
21057 
21058 
21059 
21060 
21061 
21062     debug_info := 'Check the settlement priority';
21063 
21064     if p_invoice_rec.settlement_priority is not null then
21065 
21066       begin
21067         select 'x'
21068         into l_dummy
21069         from fnd_lookups
21070         where lookup_type = 'IBY_SETTLEMENT_PRIORITY'
21071         and lookup_code = p_invoice_rec.settlement_priority
21072         and rownum = 1;
21073 
21074       exception
21075         when no_data_found then
21076           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21077                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21078                 p_invoice_rec.invoice_id,
21079                 'INVALID SETTLEMENT PRIORITY',
21080                 p_default_last_updated_by,
21081                 p_default_last_update_login,
21082                 current_calling_sequence) <> TRUE) THEN
21083             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21084               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21085                                             'insert_rejections<-'
21086                                             ||current_calling_sequence);
21087             END IF;
21088             RAISE pmt_attr_validation_failure;
21089           END IF;
21090 
21091           l_current_invoice_status := 'N';
21092 
21093        end;
21094     end if;
21095 
21096 
21097 
21098 
21099 
21100 
21101     debug_info := 'Check the external bank account id is defined';
21102 
21103     if p_invoice_rec.external_bank_account_id is not null then
21104 
21105       begin
21106         select 'x'
21107         into l_dummy
21108         from iby_ext_bank_accounts_v
21109         where ext_bank_account_id = p_invoice_rec.external_bank_account_id
21110         and rownum = 1;
21111 
21112       exception
21113         when no_data_found then
21114           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21115                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21116                 p_invoice_rec.invoice_id,
21117                 'INVALID EXTERNAL BANK ACCT ID',
21118                 p_default_last_updated_by,
21119                 p_default_last_update_login,
21120                 current_calling_sequence) <> TRUE) THEN
21121             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21122               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21123                                             'insert_rejections<-'
21124                                             ||current_calling_sequence);
21125             END IF;
21126             RAISE pmt_attr_validation_failure;
21127           END IF;
21128 
21129           l_current_invoice_status := 'N';
21130 
21131        end;
21132     end if;
21133 
21134 
21135     debug_info := 'Check the paymemt_method_code is defined';
21136 
21137     if p_invoice_rec.payment_method_code is not null then
21138        -- Bug 5448579
21139       FOR i IN AP_IMPORT_INVOICES_PKG.g_payment_method_tab.First.. AP_IMPORT_INVOICES_PKG.g_payment_method_tab.Last
21140       LOOP
21141         IF  AP_IMPORT_INVOICES_PKG.g_payment_method_tab(i).payment_method = p_invoice_rec.payment_method_code THEN
21142           l_valid_payment_method  :=  AP_IMPORT_INVOICES_PKG.g_payment_method_tab(i).payment_method;
21143           EXIT;
21144         END IF;
21145       END LOOP;
21146 
21147       debug_info := 'l_valid_payment_method: '||l_valid_payment_method;
21148       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21149         AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21150                                     debug_info);
21151       END IF;
21152 
21153       IF l_valid_payment_method IS NULL THEN
21154 
21155         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21156                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21157                 p_invoice_rec.invoice_id,
21158                 'INVALID PAY METHOD',
21159                 p_default_last_updated_by,
21160                 p_default_last_update_login,
21161                 current_calling_sequence) <> TRUE) THEN
21162           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21163               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21164                                             'insert_rejections<-'
21165                                             ||current_calling_sequence);
21166           END IF;
21167           RAISE pmt_attr_validation_failure;
21168         END IF;
21169 
21170         l_current_invoice_status := 'N';
21171 
21172       END IF;
21173 
21174     end if;
21175 
21176     /*  begin
21177         select 'x'
21178         into l_dummy
21179         from iby_payment_methods_vl --4393358
21180         where payment_method_code = p_invoice_rec.payment_method_code
21181         and rownum = 1;
21182 
21183       exception
21184         when no_data_found then
21185           IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21186                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21187                 p_invoice_rec.invoice_id,
21188                 'INVALID PAY METHOD',
21189                 p_default_last_updated_by,
21190                 p_default_last_update_login,
21191                 current_calling_sequence) <> TRUE) THEN
21192             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21193               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21194                                             'insert_rejections<-'
21195                                             ||current_calling_sequence);
21196             END IF;
21197             RAISE pmt_attr_validation_failure;
21198           END IF;
21199 
21200           l_current_invoice_status := 'N';
21201 
21202        end; */
21203 
21204 
21205 
21206 
21207     --iby's api requires the pay proc trxn type and payment function, so we
21208     --need to determine them for AP if not populated
21209 
21210     -- As per the discussion with Omar/Jayanta, we will only
21211     -- have payables payment function and no more employee expenses
21212     -- payment function.
21213 
21214     if p_invoice_rec.invoice_type_lookup_code is not null and
21215        p_invoice_rec.payment_function is null then
21216         p_invoice_rec.payment_function := 'PAYABLES_DISB';
21217     end if;
21218 
21219     /* bug 5115632 */
21220     if p_invoice_rec.invoice_type_lookup_code = 'EXPENSE REPORT'
21221       and p_invoice_rec.pay_proc_trxn_type_code is null then
21222       p_invoice_rec.pay_proc_trxn_type_code := 'EMPLOYEE_EXP';
21223     end if;
21224 
21225     if p_invoice_rec.invoice_type_lookup_code  <> 'EXPENSE REPORT'
21226       and  p_invoice_rec.pay_proc_trxn_type_code is null then
21227       if p_invoice_rec.payment_function = 'AR_CUSTOMER_REFUNDS' then
21228         p_invoice_rec.pay_proc_trxn_type_code := 'AR_CUSTOMER_REFUND';
21229       elsif p_invoice_rec.payment_function = 'LOANS_PAYMENTS' then
21230         p_invoice_rec.pay_proc_trxn_type_code := 'LOAN_PAYMENT';
21231       else
21232         p_invoice_rec.pay_proc_trxn_type_code := 'PAYABLES_DOC';
21233       end if;
21234     end if;
21235 
21236 
21237 
21238     --now get defaults...
21239 
21240     if p_invoice_rec.legal_entity_id is not null and
21241        p_invoice_rec.org_id is not null and
21242        /* Bug 8213679
21243        (p_invoice_rec.party_site_id is not null or
21244         p_invoice_rec.vendor_site_id is not null) and*/
21245 	p_invoice_rec.remit_to_supplier_id is not null and
21246 	p_invoice_rec.remit_to_supplier_site_id is not null and
21247 	--Bug 8213679
21248        p_invoice_rec.payment_currency_code is not null and
21249        p_invoice_rec.invoice_amount is not null and
21250        p_invoice_rec.payment_function is not null and
21251        p_invoice_rec.pay_proc_trxn_type_code is not null then
21252 
21253 
21254 
21255       debug_info := 'Get iby defaults';
21256 
21257       --Bug 8245830
21258       IF p_invoice_rec.invoice_type_lookup_code  <> 'PAYMENT REQUEST' THEN
21259         --Bug 8213679
21260         select party_id
21261         into l_remit_party_id
21262         from ap_suppliers
21263         where vendor_id = p_invoice_rec.remit_to_supplier_id;
21264 
21265         select party_site_id
21266         into l_remit_party_site_id
21267         from ap_supplier_sites_all
21268         where vendor_site_id = p_invoice_rec.remit_to_supplier_site_id
21269         and org_id = p_invoice_rec.org_id;
21270         --Bug 8213679
21271       ELSE
21272           l_remit_party_id      := p_invoice_rec.party_id;
21273 	  l_remit_party_site_id := p_invoice_rec.party_site_id;
21274       END IF;
21275 
21276 
21277       ap_invoices_pkg.get_payment_attributes(
21278         p_le_id                     =>p_invoice_rec.legal_entity_id,
21279         p_org_id                    =>p_invoice_rec.org_id,
21280         p_payee_party_id            =>l_remit_party_id,					--Bug 8213679
21281         p_payee_party_site_id       =>l_remit_party_site_id,				--Bug 8213679
21282         p_supplier_site_id          =>p_invoice_rec.remit_to_supplier_site_id,	--Bug 8213679
21283         p_payment_currency          =>p_invoice_rec.payment_currency_code,
21284         p_payment_amount            =>p_invoice_rec.invoice_amount,
21285         p_payment_function          =>p_invoice_rec.payment_function,
21286         p_pay_proc_trxn_type_code   =>p_invoice_rec.pay_proc_trxn_type_code,
21287 
21288         p_PAYMENT_METHOD_CODE       => l_payment_method_code,
21289         p_PAYMENT_REASON_CODE       => l_payment_reason_code,
21290         p_BANK_CHARGE_BEARER        => l_bank_charge_bearer,
21291         p_DELIVERY_CHANNEL_CODE     => l_delivery_channel_code,
21292         p_SETTLEMENT_PRIORITY       => l_settlement_priority,
21293         p_PAY_ALONE                 => l_exclusive_payment_flag,
21294         p_external_bank_account_id  => l_external_bank_account_id,
21295 
21296         p_IBY_PAYMENT_METHOD        => l_IBY_PAYMENT_METHOD,
21297         p_PAYMENT_REASON            => l_PAYMENT_REASON,
21298         p_BANK_CHARGE_BEARER_DSP    => l_BANK_CHARGE_BEARER_DSP,
21299         p_DELIVERY_CHANNEL          => l_DELIVERY_CHANNEL,
21300         p_SETTLEMENT_PRIORITY_DSP   => l_SETTLEMENT_PRIORITY_DSP,
21301         p_bank_account_num          => l_bank_account_num,
21302         p_bank_account_name         => l_bank_account_name,
21303         p_bank_branch_name          => l_bank_branch_name,
21304         p_bank_branch_num           => l_bank_branch_num,
21305         p_bank_name                 => l_bank_name,
21306         p_bank_number               => l_bank_number,
21307         p_payment_reason_comments   => l_payment_reason_comments, -- 4874927
21308         p_application_id            => p_invoice_rec.application_id);  --5115632
21309 
21310 
21311 
21312 
21313 
21314       debug_info := 'assign iby defaults to null fields';
21315 
21316       if p_invoice_rec.payment_method_code is null then
21317         p_invoice_rec.payment_method_code := l_payment_method_code;
21318       end if;
21319 
21320       if p_invoice_rec.payment_reason_code is null then
21321         p_invoice_rec.payment_reason_code := l_payment_reason_code;
21322       end if;
21323 
21324       if p_invoice_rec.bank_charge_bearer is null then
21325         p_invoice_rec.bank_charge_bearer := l_bank_charge_bearer;
21326       end if;
21327 
21328       if p_invoice_rec.delivery_channel_code is null then
21329         p_invoice_rec.delivery_channel_code := l_delivery_channel_code;
21330       end if;
21331 
21332       if p_invoice_rec.settlement_priority is null then
21333         p_invoice_rec.settlement_priority := l_settlement_priority;
21334       end if;
21335 
21336       if p_invoice_rec.exclusive_payment_flag is null then
21337         p_invoice_rec.exclusive_payment_flag := l_exclusive_payment_flag;
21338       end if;
21339 
21340       if p_invoice_rec.external_bank_account_id is null then
21341         p_invoice_rec.external_bank_account_id := l_external_bank_account_id;
21342       end if;
21343 
21344       --4874927
21345       if p_invoice_rec.payment_reason_comments is null then
21346         p_invoice_rec.payment_reason_comments := l_payment_reason_comments;
21347       end if;
21348 
21349 
21350     end if;
21351 
21352     --the payment method code is a required field so we should reject if it's
21353     --not present at this point (no default was found)
21354     if p_invoice_rec.payment_method_code is null then
21355       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21356                (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21357                 p_invoice_rec.invoice_id,
21358                 'INVALID PAY METHOD',
21359                 p_default_last_updated_by,
21360                 p_default_last_update_login,
21361                 current_calling_sequence) <> TRUE) THEN
21362             IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21363               AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21364                                             'insert_rejections<-'
21365                                             ||current_calling_sequence);
21366             END IF;
21367             RAISE pmt_attr_validation_failure;
21368       END IF;
21369       l_current_invoice_status := 'N';
21370     end if;
21371 
21372 
21373 
21374     p_current_invoice_status := l_current_invoice_status;
21375 
21376   return(true);
21377 
21378   EXCEPTION
21379 	WHEN OTHERS THEN
21380 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21381 			AP_IMPORT_UTILITIES_PKG.Print(
21382 				AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
21383 		END IF;
21384 
21385 		IF (SQLCODE < 0) THEN
21386 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21387 				AP_IMPORT_UTILITIES_PKG.Print(
21388 					AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
21389 			END IF;
21390 		END IF;
21391 		RETURN(FALSE);
21392   end v_check_payment_defaults;
21393 
21394 
21395 
21396 FUNCTION v_check_party_vendor(
21397     p_invoice_rec               IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
21398     p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
21399     p_calling_sequence          IN            VARCHAR2,
21400     p_default_last_updated_by   IN            NUMBER,
21401     p_default_last_update_login IN            NUMBER
21402     ) return boolean is
21403 
21404 l_dummy varchar2(1);
21405 l_current_invoice_status varchar2(1):='Y';
21406 debug_info                  VARCHAR2(500);
21407 current_calling_sequence    VARCHAR2(2000);
21408 vendor_party_failure        exception;
21409 
21410 begin
21411 
21412   current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_party_vendor<-'
21413 					||P_calling_sequence;
21414   debug_info := 'Check vendor and party info are consistent';
21415 
21416 
21417 
21418 
21419   --if the vendor and party are populated, I think we should make sure they are
21420   --consistent, the same goes for vedor site and party site
21421   -- Release won't be able to seed a rejection for the 2 cases below before the
21422   -- freeze.  So for now I am using existin ones.
21423 
21424   if p_invoice_rec.party_id is not null and p_invoice_rec.vendor_id is not null then
21425     begin
21426       select 'x'
21427       into l_dummy
21428       from po_vendors
21429       where vendor_id = p_invoice_rec.vendor_id
21430       and party_id = p_invoice_rec.party_id;
21431     exception
21432       when no_data_found then
21433         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21434              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21435               p_invoice_rec.invoice_id,
21436               'INCONSISTENT SUPPLIER',
21437               p_default_last_updated_by,
21438               p_default_last_update_login,
21439               current_calling_sequence) <> TRUE) THEN
21440           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21441             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21442                                           'insert_rejections<-'
21443                                           ||current_calling_sequence);
21444           END IF;
21445           RAISE vendor_party_failure;
21446         END IF;
21447       l_current_invoice_status := 'N';
21448     end;
21449   end if;
21450 
21451 
21452 
21453   if p_invoice_rec.party_site_id is not null and
21454      p_invoice_rec.vendor_site_id is not null then
21455     begin
21456       select 'x'
21457       into l_dummy
21458       from po_vendor_sites
21459       where vendor_site_id = p_invoice_rec.vendor_site_id
21460       and party_site_id = p_invoice_rec.party_site_id;
21461     exception
21462       when no_data_found then
21463         IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21464              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21465               p_invoice_rec.invoice_id,
21466               'INCONSISTENT SUPPL SITE',
21467               p_default_last_updated_by,
21468               p_default_last_update_login,
21469               current_calling_sequence) <> TRUE) THEN
21470           IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21471             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21472                                           'insert_rejections<-'
21473                                           ||current_calling_sequence);
21474           END IF;
21475           RAISE vendor_party_failure;
21476         END IF;
21477       l_current_invoice_status := 'N';
21478     end;
21479   end if;
21480 
21481 
21482 
21483 
21484 
21485   --according to Shelley, we want to populate a negative application
21486   --id when we have party info but no vendor info
21487 
21488   if p_invoice_rec.party_id is not null and p_invoice_rec.vendor_id is null then
21489     p_invoice_rec.vendor_id := -1 * p_invoice_rec.application_id;
21490   end if;
21491 
21492   if p_invoice_rec.party_site_id is not null and p_invoice_rec.vendor_site_id is null then
21493     p_invoice_rec.vendor_site_id := -1 * p_invoice_rec.application_id;
21494   end if;
21495 
21496 
21497 
21498 
21499   --if we just have vendor info then also populate the party info
21500   if p_invoice_rec.vendor_site_id is not null and p_invoice_rec.party_site_id is null
21501      and nvl(p_invoice_rec.invoice_type_lookup_code, 'STANDARD') <> 'EXPENSE REPORT' then
21502     Begin
21503       select party_site_id
21504       into p_invoice_rec.party_site_id
21505       from po_vendor_sites
21506       where vendor_site_id = p_invoice_rec.vendor_site_id;
21507     Exception
21508       when no_data_found then
21509       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21510              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21511               p_invoice_rec.invoice_id,
21512               'INCONSISTENT SUPPL SITE',
21513               p_default_last_updated_by,
21514               p_default_last_update_login,
21515               current_calling_sequence) <> TRUE) THEN
21516         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21517             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21518                                           'insert_rejections<-'
21519                                           ||current_calling_sequence);
21520         END IF;
21521         RAISE vendor_party_failure;  --bug6367302
21522       END IF;
21523       --RAISE vendor_party_failure;
21524     End;
21525   end if;
21526 
21527   if p_invoice_rec.vendor_id is not null and p_invoice_rec.party_id is null then
21528     Begin
21529       select party_id
21530       into p_invoice_rec.party_id
21531       from po_vendors
21532       where vendor_id = p_invoice_rec.vendor_id;
21533     Exception
21534       when no_data_found then
21535       IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21536              (AP_IMPORT_INVOICES_PKG.g_invoices_table,
21537               p_invoice_rec.invoice_id,
21538               'INCONSISTENT SUPPLIER',
21539               p_default_last_updated_by,
21540               p_default_last_update_login,
21541               current_calling_sequence) <> TRUE) THEN
21542         IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21543             AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21544                                           'insert_rejections<-'
21545                                           ||current_calling_sequence);
21546         END IF;
21547         RAISE vendor_party_failure;  --bug6367302
21548       END IF;
21549       --RAISE vendor_party_failure;
21550     End;
21551   end if;
21552 
21553 
21554 
21555   p_current_invoice_status := l_current_invoice_status;
21556   return(true);
21557 
21558 EXCEPTION
21559   WHEN OTHERS THEN
21560 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21561 			AP_IMPORT_UTILITIES_PKG.Print(
21562 				AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
21563 		END IF;
21564 
21565 		IF (SQLCODE < 0) THEN
21566 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21567 				AP_IMPORT_UTILITIES_PKG.Print(
21568 					AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
21569 			END IF;
21570 		END IF;
21571 		RETURN(FALSE);
21572 end v_check_party_vendor;
21573 
21574 
21575 --bugfix:5565310
21576 FUNCTION v_check_line_get_po_tax_attr(
21577 		p_invoice_rec IN AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
21578                 p_invoice_lines_rec IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_line_info_rec,
21579 	        p_calling_sequence IN VARCHAR2) return boolean  IS
21580 
21581  l_ref_doc_application_id      zx_transaction_lines_gt.ref_doc_application_id%TYPE;
21582  l_ref_doc_entity_code         zx_transaction_lines_gt.ref_doc_entity_code%TYPE;
21583  l_ref_doc_event_class_code    zx_transaction_lines_gt.ref_doc_event_class_code%TYPE;
21584  l_ref_doc_line_quantity       zx_transaction_lines_gt.ref_doc_line_quantity%TYPE;
21585  l_po_header_curr_conv_rat     po_headers_all.rate%TYPE;
21586  l_ref_doc_trx_level_type      zx_transaction_lines_gt.ref_doc_trx_level_type%TYPE;
21587  l_po_header_curr_conv_rate    po_headers_all.rate%TYPE;
21588  l_uom_code                    mtl_units_of_measure.uom_code%TYPE;
21589  l_ref_doc_trx_id              po_headers_all.po_header_id%TYPE;
21590  l_error_code                  varchar2(2000);
21591  current_calling_sequence VARCHAR2(2000);
21592  l_success		       boolean;
21593  l_intended_use                  zx_lines_det_factors.line_intended_use%type;
21594  l_product_type                  zx_lines_det_factors.product_type%type;
21595  l_product_category              zx_lines_det_factors.product_category%type;
21596  l_product_fisc_class            zx_lines_det_factors.product_fisc_classification%type;
21597  l_user_defined_fisc_class       zx_lines_det_factors.user_defined_fisc_class%type;
21598  l_assessable_value              zx_lines_det_factors.assessable_value%type;
21599  l_dflt_tax_class_code           zx_transaction_lines_gt.input_tax_classification_code%type;
21600  l_dummy			 number;
21601  debug_info			 varchar2(1000);
21602 
21603 BEGIN
21604 
21605 
21606     IF (p_invoice_lines_rec.primary_intended_use IS NULL OR
21607         p_invoice_lines_rec.product_fisc_classification IS NULL OR
21608 	p_invoice_lines_rec.product_type IS NULL OR
21609 	p_invoice_lines_rec.product_category IS NULL OR
21610 	p_invoice_lines_rec.user_defined_fisc_class IS NULL OR
21611 	p_invoice_lines_rec.assessable_value IS NULL OR
21612 	p_invoice_lines_rec.tax_classification_code IS NULL) THEN
21613 
21614 	debug_info := 'Call Ap_Etx_Utility_Pkg.Get_PO_Info';
21615 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21616 	    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21617 	                                      debug_info);
21618         END IF;
21619 
21620         l_success := AP_ETAX_UTILITY_PKG.Get_PO_Info(
21621 	                  P_Po_Line_Location_Id         => p_invoice_lines_rec.po_line_location_id,
21622 			  P_PO_Distribution_Id          => null,
21623 			  P_Application_Id              => l_ref_doc_application_id,
21624 			  P_Entity_code                 => l_ref_doc_entity_code,
21625 			  P_Event_Class_Code            => l_ref_doc_event_class_code,
21626 			  P_PO_Quantity                 => l_ref_doc_line_quantity,
21627 			  P_Product_Org_Id              => l_dummy,
21628 			  P_Po_Header_Id                => l_ref_doc_trx_id,
21629 			  P_Po_Header_curr_conv_rate    => l_po_header_curr_conv_rate,
21630 			  P_Uom_Code                    => l_uom_code,
21631 			  P_Dist_Qty                    => l_dummy,
21632 			  P_Ship_Price                  => l_dummy,
21633 			  P_Error_Code                  => l_error_code,
21634 			  P_Calling_Sequence            => current_calling_sequence);
21635 
21636 	 debug_info := 'Call ap_etx_servies_pkg.get_po_tax_attributes';
21637 	 IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21638 	     AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21639 	                                       debug_info);
21640          END IF;
21641 
21642          AP_Etax_Services_Pkg.Get_Po_Tax_Attributes(
21643 	                  p_application_id              => l_ref_doc_application_id,
21644 			  p_org_id                      => p_invoice_lines_rec.org_id,
21645 			  p_entity_code                 => l_ref_doc_entity_code,
21646 			  p_event_class_code            => l_ref_doc_event_class_code,
21647 			  p_trx_level_type              => 'SHIPMENT',
21648 			  p_trx_id                      => l_ref_doc_trx_id,
21649 			  p_trx_line_id                 => p_invoice_lines_rec.po_line_location_id,
21650 			  x_line_intended_use           => l_intended_use,
21651 			  x_product_type                => l_product_type,
21652 			  x_product_category            => l_product_category,
21653 			  x_product_fisc_classification => l_product_fisc_class,
21654 			  x_user_defined_fisc_class     => l_user_defined_fisc_class,
21655 			  x_assessable_value            => l_assessable_value,
21656 			  x_tax_classification_code     => l_dflt_tax_class_code
21657 			  );
21658 
21659 	  debug_info := 'populate the lines record with tax attr info';
21660 	  IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21661 	        AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21662 	                                         debug_info);
21663 	  END IF;
21664 
21665           IF (p_invoice_lines_rec.primary_intended_use IS NULL) THEN
21666               p_invoice_lines_rec.primary_intended_use := l_intended_use;
21667 	  END IF;
21668 
21669 	  IF (p_invoice_lines_rec.product_type IS NULL) THEN
21670 	      p_invoice_lines_rec.product_type := l_product_type;
21671 	  END IF;
21672 
21673 	  IF (p_invoice_lines_rec.product_category IS NULL) THEN
21674 	      p_invoice_lines_rec.product_category := l_product_category;
21675 	  END IF;
21676 
21677 	  IF (p_invoice_lines_rec.product_fisc_classification IS NULL) THEN
21678 	      p_invoice_lines_rec.product_fisc_classification:= l_product_fisc_class;
21679 	  END IF;
21680 
21681 	  IF (p_invoice_lines_rec.USER_DEFINED_FISC_CLASS IS NULL) THEN
21682 	    p_invoice_lines_rec.USER_DEFINED_FISC_CLASS := l_user_defined_fisc_class;
21683 	  END IF;
21684 
21685 	  IF (p_invoice_lines_rec.assessable_value IS NULL) THEN
21686 	     p_invoice_lines_rec.assessable_value := l_assessable_value;
21687 	  END IF;
21688 
21689 	  IF (p_invoice_lines_rec.tax_classification_code IS NULL) THEN
21690 	      p_invoice_lines_rec.tax_classification_code := l_dflt_tax_class_code;
21691 	  END IF;
21692 
21693     END IF;
21694 
21695    return(true);
21696 
21697 EXCEPTION
21698   WHEN OTHERS THEN
21699       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21700            AP_IMPORT_UTILITIES_PKG.Print(
21701                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
21702        END IF;
21703 
21704   IF (SQLCODE < 0) THEN
21705     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21706         AP_IMPORT_UTILITIES_PKG.Print(
21707             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
21708      END IF;
21709   END IF;
21710   RETURN(FALSE);
21711 
21712 
21713 END v_check_line_get_po_tax_attr;
21714 
21715 --bug# 6989166 starts
21716 FUNCTION v_check_ship_to_location_code(
21717 		p_invoice_rec	IN  AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
21718 		p_invoice_line_rec  IN AP_IMPORT_INVOICES_PKG.r_line_info_rec,
21719                 p_default_last_updated_by      IN            NUMBER,
21720 		p_default_last_update_login    IN            NUMBER,
21721 		p_current_invoice_status	IN OUT NOCOPY VARCHAR2,
21722 	        p_calling_sequence IN VARCHAR2) return boolean  IS
21723 
21724   Cursor c_ship_to_location (p_ship_to_loc_code HR_LOCATIONS.LOCATION_CODE%TYPE) Is
21725   Select ship_to_location_id
21726   From   hr_locations
21727   Where  location_code = p_ship_to_loc_code
21728   and	nvl(ship_to_site_flag, 'N') = 'Y';
21729 
21730   l_ship_to_location_id  ap_supplier_sites_all.ship_to_location_id%type;
21731   current_calling_sequence VARCHAR2(2000);
21732   debug_info			 varchar2(1000);
21733   ship_to_location_code_failure EXCEPTION;
21734   l_current_invoice_status    VARCHAR2(1) := 'Y';
21735 
21736 BEGIN
21737 
21738 	current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_ship_to_location_code<-'
21739 				||P_calling_sequence;
21740 	debug_info := 'Check valid ship to location code';
21741 
21742 
21743  	Open  c_ship_to_location (p_invoice_line_rec.ship_to_location_code);
21744 	Fetch c_ship_to_location
21745 	Into  l_ship_to_location_id;
21746 
21747 
21748 	IF (c_ship_to_location%NOTFOUND) THEN
21749 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections
21750 			(AP_IMPORT_INVOICES_PKG.g_invoices_table,
21751 						p_invoice_rec.invoice_id,
21752 						'INVALID LOCATION CODE',
21753 					        p_default_last_updated_by,
21754 						p_default_last_update_login,
21755 						current_calling_sequence) <> TRUE) THEN
21756 
21757 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21758 			    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21759 							  'insert_rejections<-'
21760 							  ||current_calling_sequence);
21761 
21762 		        END IF;
21763 
21764 			Close c_ship_to_location;
21765 			RAISE ship_to_location_code_failure;
21766 
21767 		END IF;
21768 		l_current_invoice_status := 'N';
21769 	END IF;
21770 
21771    Close c_ship_to_location;
21772 
21773    p_current_invoice_status := l_current_invoice_status;
21774 
21775    return(true);
21776 
21777 EXCEPTION
21778   WHEN OTHERS THEN
21779       IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21780            AP_IMPORT_UTILITIES_PKG.Print(
21781                AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
21782        END IF;
21783 
21784   IF (SQLCODE < 0) THEN
21785     IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
21786         AP_IMPORT_UTILITIES_PKG.Print(
21787             AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
21788      END IF;
21789   END IF;
21790   RETURN(FALSE);
21791 
21792 
21793 END v_check_ship_to_location_code;
21794 --bug# 6989166 ends
21795 
21796 FUNCTION v_check_invalid_remit_supplier(
21797              p_invoice_rec      IN OUT NOCOPY AP_IMPORT_INVOICES_PKG.r_invoice_info_rec,
21798              p_default_last_updated_by     IN            NUMBER,
21799              p_default_last_update_login   IN            NUMBER,
21800              p_current_invoice_status      IN OUT NOCOPY VARCHAR2,
21801              p_calling_sequence           IN            VARCHAR2)
21802     RETURN BOOLEAN IS
21803 
21804   current_calling_sequence VARCHAR2(2000);
21805   debug_info			varchar2(1000);
21806 
21807   l_party_id				NUMBER := NULL;
21808 
21809   l_remit_supplier_name       VARCHAR2(240) := NULL;
21810   l_remit_supplier_id            NUMBER := NULL;
21811   l_remit_supplier_num            VARCHAR2(30) := NULL;
21812   l_remit_supplier_site         VARCHAR2(240) := NULL;
21813   l_remit_supplier_site_id     NUMBER := NULL;
21814   l_remit_party_id            NUMBER := NULL;
21815   l_remit_party_site_id            NUMBER := NULL;
21816   l_relationship_id           NUMBER;
21817   l_result                    VARCHAR2(25);
21818   l_remit_supplier_name_flag       VARCHAR2(1) := 'T';
21819   l_remit_supplier_id_flag            VARCHAR2(1) := 'T';
21820   l_remit_supplier_num_flag            VARCHAR2(1) := 'T';
21821   l_remit_supplier_site_flag         VARCHAR2(1) := 'T';
21822   l_remit_supplier_site_id_flag     VARCHAR2(1) := 'T';
21823 
21824   invalid_remit_supplier_failure  EXCEPTION;
21825 
21826 BEGIN
21827 	current_calling_sequence := 'AP_IMPORT_VALIDATION_PKG.v_check_invalid_remit_supplier<-'
21828 					      ||P_calling_sequence;
21829 	-------------------------------------------------------------------
21830 	debug_info := 'Check valid remit to supplier details';
21831 	-------------------------------------------------------------------
21832 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21833 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21834 					  debug_info);
21835 	END IF;
21836 
21837 	-------------------------------------------------------------------
21838 	debug_info := 'Remit to supplier Name '||p_invoice_rec.remit_to_supplier_name;
21839 	-------------------------------------------------------------------
21840 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21841 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21842 					  debug_info);
21843 	END IF;
21844 
21845 	-------------------------------------------------------------------
21846 	debug_info := 'Remit to supplier Id '||p_invoice_rec.remit_to_supplier_id;
21847 	-------------------------------------------------------------------
21848 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21849 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21850 					  debug_info);
21851 	END IF;
21852 
21853 	-------------------------------------------------------------------
21854 	debug_info := 'Remit to supplier Site Id '||p_invoice_rec.remit_to_supplier_site_id;
21855 	-------------------------------------------------------------------
21856 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21857 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21858 					  debug_info);
21859 	END IF;
21860 
21861 	-------------------------------------------------------------------
21862 	debug_info := 'Remit to supplier Site Name '||p_invoice_rec.remit_to_supplier_site;
21863 	-------------------------------------------------------------------
21864 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21865 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21866 					  debug_info);
21867 	END IF;
21868 
21869 	If(p_invoice_rec.remit_to_supplier_name IS NOT NULL) then
21870 		select vendor_name
21871 		into l_remit_supplier_name
21872 		from ap_suppliers
21873 		where vendor_name = p_invoice_rec.remit_to_supplier_name;
21874 
21875 		If (l_remit_supplier_name is null) then
21876 		    l_remit_supplier_name_flag := 'F';
21877 		end if;
21878 	END if;
21879 
21880         -------------------------------------------------------------------
21881         debug_info := 'If Remit to supplier Name '||l_remit_supplier_name;
21882         -------------------------------------------------------------------
21883 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21884 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21885 					  debug_info);
21886 	END IF;
21887 
21888 	if(p_invoice_rec.remit_to_supplier_id IS NOT NULL) then
21889 		select vendor_id
21890 		into l_remit_supplier_id
21891 		from ap_suppliers
21892 		where vendor_id = p_invoice_rec.remit_to_supplier_id;
21893 
21894 		If (l_remit_supplier_id is null) then
21895 			l_remit_supplier_id_flag := 'F';
21896 		end if;
21897 	END if;
21898 
21899         -------------------------------------------------------------------
21900         debug_info := 'If Remit to supplier Id '||l_remit_supplier_id;
21901         -------------------------------------------------------------------
21902 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21903 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21904 					  debug_info);
21905 	END IF;
21906 
21907 	if(p_invoice_rec.remit_to_supplier_num IS NOT NULL) then
21908 		select segment1
21909 		into l_remit_supplier_num
21910 		from ap_suppliers
21911 		where segment1= p_invoice_rec.remit_to_supplier_num;	-- bug 7836976
21912 
21913 		If (l_remit_supplier_num is null) then
21914 			l_remit_supplier_num_flag := 'F';
21915 		end if;
21916 	END if;
21917 
21918         -------------------------------------------------------------------
21919         debug_info := 'If Remit to supplier Num '||l_remit_supplier_num;
21920         -------------------------------------------------------------------
21921 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21922 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21923 					  debug_info);
21924 	END IF;
21925 
21926 	if(p_invoice_rec.remit_to_supplier_site_id IS NOT NULL) then
21927 		select vendor_site_id
21928 		into l_remit_supplier_site_id
21929 		from ap_supplier_sites_all
21930 		where vendor_site_id = p_invoice_rec.remit_to_supplier_site_id
21931 		and org_id = p_invoice_rec.org_id;
21932 
21933 		If (l_remit_supplier_site_id is null) then
21934 		    l_remit_supplier_site_id_flag := 'F';
21935 		end if;
21936 	END if;
21937 
21938         -------------------------------------------------------------------
21939         debug_info := 'If Remit to supplier Site Id '||l_remit_supplier_site_id;
21940         -------------------------------------------------------------------
21941 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21942 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21943 					  debug_info);
21944 	END IF;
21945 
21946 	if(p_invoice_rec.remit_to_supplier_site IS NOT NULL) then
21947 		If (l_remit_supplier_site_id IS NOT NULL) then
21948 			select vendor_site_code
21949 			 into l_remit_supplier_site
21950 			from ap_supplier_sites_all
21951 			where vendor_site_code = p_invoice_rec.remit_to_supplier_site
21952 			and org_id = p_invoice_rec.org_id
21953 			and vendor_site_id = p_invoice_rec.remit_to_supplier_site_id;
21954 		elsif(l_remit_supplier_id IS NOT NULL) then
21955 			select vendor_site_code
21956 			 into l_remit_supplier_site
21957 			from ap_supplier_sites_all
21958 			where vendor_site_code = p_invoice_rec.remit_to_supplier_site
21959 			and org_id = p_invoice_rec.org_id
21960 			and vendor_id = p_invoice_rec.remit_to_supplier_id;
21961 		elsif(l_remit_supplier_num IS NOT NULL) then
21962 			select a.vendor_site_code
21963 			 into l_remit_supplier_site
21964 			from ap_supplier_sites_all a,
21965 				ap_suppliers b
21966 			where a.vendor_site_code = p_invoice_rec.remit_to_supplier_site
21967 			and a.org_id = p_invoice_rec.org_id
21968 			and a.vendor_id = b.vendor_id
21969 			and b.segment1 = p_invoice_rec.remit_to_supplier_num;
21970 		end if;
21971 
21972 		If (l_remit_supplier_site is null) then
21973 		    l_remit_supplier_site_flag := 'F';
21974 		end if;
21975 	end if;
21976 
21977         -------------------------------------------------------------------
21978         debug_info := 'If Remit to supplier Site '||l_remit_supplier_site;
21979         -------------------------------------------------------------------
21980 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21981 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21982 					  debug_info);
21983 	END IF;
21984 
21985 	-------------------------------------------------------------------
21986 	debug_info := 'Rejection Flags ';
21987 	-------------------------------------------------------------------
21988 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21989 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21990 					  debug_info);
21991 	END IF;
21992 
21993 	-------------------------------------------------------------------
21994 	debug_info := 'Suppier Name Rejection Flags '||l_remit_supplier_name_flag;
21995 	-------------------------------------------------------------------
21996 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
21997 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
21998 					  debug_info);
21999 	END IF;
22000 
22001 	-------------------------------------------------------------------
22002 	debug_info := 'Supplier Id Rejection Flags '||l_remit_supplier_id_flag;
22003 	-------------------------------------------------------------------
22004 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22005 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22006 					  debug_info);
22007 	END IF;
22008 
22009 	-------------------------------------------------------------------
22010 	debug_info := 'Supplier Site Id Rejection Flags '||l_remit_supplier_site_id_flag;
22011 	-------------------------------------------------------------------
22012 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22013 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22014 					  debug_info);
22015 	END IF;
22016 
22017 	-------------------------------------------------------------------
22018 	debug_info := 'Supplier Site Rejection Flags '||l_remit_supplier_site_flag;
22019 	-------------------------------------------------------------------
22020 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22021 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22022 					  debug_info);
22023 	END IF;
22024 
22025 	IF (l_remit_supplier_name_flag = 'F') THEN
22026 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22027 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
22028 						p_invoice_rec.invoice_id,
22029 						'INVALID REMIT TO SUPPLIER NAME',
22030 						p_default_last_updated_by,
22031 						p_default_last_update_login,
22032 						current_calling_sequence) <> TRUE) THEN
22033 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22034 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22035 			'insert_rejections<-'||current_calling_sequence);
22036 		   END IF;
22037 
22038 		END IF;
22039 
22040 		RAISE invalid_remit_supplier_failure;
22041 
22042 	ELSIF (l_remit_supplier_id_flag = 'F') THEN
22043 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22044 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
22045 						p_invoice_rec.invoice_id,
22046 						 'INVALID REMIT TO SUPPLIER ID',
22047 						p_default_last_updated_by,
22048 						p_default_last_update_login,
22049 						current_calling_sequence) <> TRUE) THEN
22050 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22051 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22052 			'insert_rejections<-'||current_calling_sequence);
22053 		   END IF;
22054 
22055 		END IF;
22056 
22057 		RAISE invalid_remit_supplier_failure;
22058 
22059 	ELSIF (l_remit_supplier_num_flag = 'F') THEN
22060 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22061 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
22062 						p_invoice_rec.invoice_id,
22063 						 'INVALID REMIT TO SUPPLIER NUM',
22064 						p_default_last_updated_by,
22065 						p_default_last_update_login,
22066 						current_calling_sequence) <> TRUE) THEN
22067 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22068 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22069 			'insert_rejections<-'||current_calling_sequence);
22070 		   END IF;
22071 
22072 		END IF;
22073 
22074 		RAISE invalid_remit_supplier_failure;
22075 
22076 	ELSIF (l_remit_supplier_site_id_flag = 'F') THEN
22077 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22078 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
22079 						p_invoice_rec.invoice_id,
22080 						'INVALID REMIT TO SUPP SITE ID',
22081 						p_default_last_updated_by,
22082 						p_default_last_update_login,
22083 						current_calling_sequence) <> TRUE) THEN
22084 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22085 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22086 			'insert_rejections<-'||current_calling_sequence);
22087 		   END IF;
22088 
22089 		END IF;
22090 
22091 		RAISE invalid_remit_supplier_failure;
22092 
22093 	ELSIF (l_remit_supplier_site_flag = 'F') THEN
22094 		IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22095 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
22096 						p_invoice_rec.invoice_id,
22097 						'INVALID REMIT TO SUPPLIER SITE',
22098 						p_default_last_updated_by,
22099 						p_default_last_update_login,
22100 						current_calling_sequence) <> TRUE) THEN
22101 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22102 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22103 			'insert_rejections<-'||current_calling_sequence);
22104 		   END IF;
22105 
22106 		END IF;
22107 
22108 		RAISE invalid_remit_supplier_failure;
22109 
22110 	END IF;
22111 
22112 	IF (p_invoice_rec.party_id is null AND p_invoice_rec.vendor_id is not null) THEN
22113 		SELECT party_id
22114 		INTO l_party_id
22115 		FROM ap_suppliers
22116 		WHERE vendor_id = p_invoice_rec.vendor_id;
22117 	ELSIF (p_invoice_rec.party_id is null AND p_invoice_rec.vendor_num is not null) THEN
22118 		SELECT party_id
22119 		INTO l_party_id
22120 		FROM ap_suppliers
22121 		WHERE segment1 = p_invoice_rec.vendor_num;
22122 	ELSIF (p_invoice_rec.party_id is null AND p_invoice_rec.vendor_name is not null) THEN
22123 		SELECT party_id
22124 		INTO l_party_id
22125 		FROM ap_suppliers
22126 		WHERE vendor_name = p_invoice_rec.vendor_name;
22127 	ELSIF (p_invoice_rec.party_id is not null) THEN
22128 		l_party_id := p_invoice_rec.party_id;
22129 	END IF;
22130 
22131 	-------------------------------------------------------------------
22132 	debug_info := 'Data To IBY ';
22133 	-------------------------------------------------------------------
22134 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22135 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22136 					  debug_info);
22137 	END IF;
22138 
22139 	-------------------------------------------------------------------
22140 	debug_info := 'Party Id '||l_party_id;
22141 	-------------------------------------------------------------------
22142 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22143 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22144 					  debug_info);
22145 	END IF;
22146 
22147 	-------------------------------------------------------------------
22148 	debug_info := 'Vendor Site id '||p_invoice_rec.vendor_site_id;
22149 	-------------------------------------------------------------------
22150 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22151 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22152 					  debug_info);
22153 	END IF;
22154 
22155 	-------------------------------------------------------------------
22156 	debug_info := 'Invoice Date '||p_invoice_rec.invoice_date;
22157 	-------------------------------------------------------------------
22158 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22159 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22160 					  debug_info);
22161 	END IF;
22162 
22163 	-------------------------------------------------------------------
22164 	debug_info := 'Invoice Date '||p_invoice_rec.invoice_date;
22165 	-------------------------------------------------------------------
22166 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22167 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22168 					  debug_info);
22169 	END IF;
22170 
22171 	IF (p_invoice_rec.remit_to_supplier_id is not null) THEN
22172 		SELECT party_id
22173 		INTO l_remit_party_id
22174 		FROM ap_suppliers
22175 		WHERE vendor_id = p_invoice_rec.remit_to_supplier_id;
22176 	END IF;
22177 
22178 	-------------------------------------------------------------------
22179 	debug_info := 'Remit Party Id '||l_remit_party_id;
22180 	-------------------------------------------------------------------
22181 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22182 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22183 					  debug_info);
22184 	END IF;
22185 
22186 	l_relationship_id := p_invoice_rec.relationship_id;	-- bug 8224788
22187 
22188 	IBY_EXT_PAYEE_RELSHIPS_PKG.import_Ext_Payee_Relationship(
22189 		p_party_id => l_party_id,
22190 		p_supplier_site_id => p_invoice_rec.vendor_site_id,
22191 		p_date => p_invoice_rec.invoice_date,
22192 		x_result => l_result,
22193 		x_remit_party_id => l_remit_party_id,
22194 		x_remit_supplier_site_id => l_remit_supplier_site_id,
22195 		x_relationship_id => l_relationship_id
22196 		);
22197 
22198 	-------------------------------------------------------------------
22199 	debug_info := 'Data From IBY ';
22200 	-------------------------------------------------------------------
22201 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22202 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22203 					  debug_info);
22204 	END IF;
22205 
22206 	-------------------------------------------------------------------
22207 	debug_info := 'x_result : ' || l_result;
22208 	-------------------------------------------------------------------
22209 	IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22210 		AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22211 					  debug_info);
22212 	END IF;
22213 
22214 	IF (l_result = FND_API.G_TRUE) THEN
22215 
22216 	-- Bug 7675510
22217 	-- Added AND condition so as to Select data from ap_supplier_sites_all when
22218 	-- l_remit_supplier_site_id is having a Positive value
22219 	-- Negative value of l_remit_supplier_site_id does not have any data in ap_supplier_sites_all
22220 	-- This negative value is assigned to p_invoice_rec.vendor_site_id in
22221 	-- FUNCTION v_check_party_vendor earlier in this package
22222 
22223 	   IF (l_remit_supplier_site_id is not null AND
22224 		l_remit_supplier_site_id > 0) THEN
22225 	-- Bug 7675510 ends
22226 		SELECT vendor_site_id, vendor_site_code
22227 		INTO l_remit_supplier_site_id, l_remit_supplier_site
22228 		FROM ap_supplier_sites_all
22229 		WHERE vendor_site_id = l_remit_supplier_site_id
22230 		and org_id = p_invoice_rec.org_id;
22231 	   END IF;
22232 
22233 	   p_invoice_rec.remit_to_supplier_site_id := l_remit_supplier_site_id;
22234 	   p_invoice_rec.remit_to_supplier_site := l_remit_supplier_site;
22235 
22236 	   -------------------------------------------------------------------
22237 	   debug_info := 'Remit To Supplier Site Id  '||l_remit_supplier_site_id;
22238 	   -------------------------------------------------------------------
22239 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22240 		   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22241 					      debug_info);
22242 	   END IF;
22243 
22244            -------------------------------------------------------------------
22245            debug_info := 'Remit To Supplier Site '||l_remit_supplier_site;
22246            -------------------------------------------------------------------
22247 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22248 		    AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22249 					     debug_info);
22250 	   END IF;
22251 
22252 	-- Bug 7675510
22253 	-- Added the invoice_type_lookup_code condition to populate the l_remit_supplier_id,
22254 	-- l_remit_supplier_name, l_remit_supplier_num from HZ_PARTIES table in case of PAYMENT REQUEST
22255 	-- since the data is not available in AP_SUPPLIERS table for PAYMENT REQUEST type
22256 
22257            -------------------------------------------------------------------
22258            debug_info := 'Invoice Type Lookup Code '||p_invoice_rec.invoice_type_lookup_code;
22259            -------------------------------------------------------------------
22260 
22261 	   IF (p_invoice_rec.invoice_type_lookup_code = 'PAYMENT REQUEST') THEN
22262 
22263 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22264 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
22265 		END IF;
22266 
22267 		IF (l_remit_party_id is not null) THEN
22268                     --Bug 7860631 Removed the party_id field into the supplier_id field.
22269                         SELECT party_name, party_number
22270                         INTO   l_remit_supplier_name, l_remit_supplier_num
22271                         FROM hz_parties
22272                         WHERE party_id = l_remit_party_id;
22273                    --Bug 7860631 Defaulting the remit_supplier_id from the invoice
22274                    l_remit_supplier_id :=p_invoice_rec.vendor_id;
22275  		END IF;
22276 
22277 	   ELSE
22278 
22279 	   -- bug 7629217 starts- dcshanmu - changed l_party_id to l_remit_party_id
22280 		   IF (l_remit_party_id is not null) THEN
22281 			SELECT vendor_id, vendor_name, segment1
22282 			INTO l_remit_supplier_id, l_remit_supplier_name, l_remit_supplier_num
22283 			FROM ap_suppliers
22284 			WHERE party_id = l_remit_party_id;
22285 		END IF;
22286 	   -- bug 7629217 starts- dcshanmu ends
22287 
22288 	   END IF ;
22289 	-- Bug 7675510 ends
22290 
22291 	   p_invoice_rec.remit_to_supplier_id := l_remit_supplier_id;
22292 	   p_invoice_rec.remit_to_supplier_name := l_remit_supplier_name;
22293 	   p_invoice_rec.remit_to_supplier_num := l_remit_supplier_num;
22294 	   p_invoice_rec.relationship_id := l_relationship_id;
22295 
22296 	   p_current_invoice_status := 'Y';
22297 
22298 	   -------------------------------------------------------------------
22299 	   debug_info := 'Remit To Party Id  '||l_remit_party_id;
22300 	   -------------------------------------------------------------------
22301 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22302 		   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22303 					     debug_info);
22304 	   END IF;
22305 
22306 	   -------------------------------------------------------------------
22307 	   debug_info := 'Remit To Supplier Id '||l_remit_supplier_id;
22308 	   -------------------------------------------------------------------
22309 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22310 		   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22311 					     debug_info);
22312 	   END IF;
22313 
22314            -------------------------------------------------------------------
22315            debug_info := 'Remit To Supplier '||l_remit_supplier_name;
22316            -------------------------------------------------------------------
22317 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22318 		   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22319 					     debug_info);
22320 	   END IF;
22321 
22322 	   -----------------------------------------------------------------------
22323 	   debug_info := 'Remit To Supplier Num '||l_remit_supplier_num;
22324 	   -----------------------------------------------------------------------
22325 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22326 		   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22327 					    debug_info);
22328 	   END IF;
22329 
22330 	   -------------------------------------------------------------------
22331 	   debug_info := 'Relationship Id '||l_relationship_id;
22332 	   -------------------------------------------------------------------
22333 	   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22334 		   AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22335 					     debug_info);
22336 	   END IF;
22337 
22338 	ELSE
22339 
22340 	    IF (AP_IMPORT_UTILITIES_PKG.insert_rejections(
22341 						AP_IMPORT_INVOICES_PKG.g_invoices_table,
22342 						p_invoice_rec.invoice_id,
22343 						'INVALID THIRD PARTY RELATION',
22344 						p_default_last_updated_by,
22345 						p_default_last_update_login,
22346 						current_calling_sequence) <> TRUE) THEN
22347 		   IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') then
22348 			AP_IMPORT_UTILITIES_PKG.Print(AP_IMPORT_INVOICES_PKG.g_debug_switch,
22349 			'insert_rejections<-'||current_calling_sequence);
22350 		   END IF;
22351 	    END IF;
22352 
22353 	    RAISE invalid_remit_supplier_failure;
22354 	END IF;
22355 
22356 	RETURN TRUE;
22357 
22358 EXCEPTION
22359 	WHEN invalid_remit_supplier_failure THEN
22360 
22361 		p_current_invoice_status := 'N';
22362 		RETURN FALSE;
22363 	WHEN OTHERS THEN
22364 		p_current_invoice_status := 'N';
22365 
22366 		IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22367 		   AP_IMPORT_UTILITIES_PKG.Print(
22368 		       AP_IMPORT_INVOICES_PKG.g_debug_switch,debug_info);
22369 		END IF;
22370 
22371 		IF (SQLCODE < 0) THEN
22372 			IF (AP_IMPORT_INVOICES_PKG.g_debug_switch = 'Y') THEN
22373 			AP_IMPORT_UTILITIES_PKG.Print(
22374 			    AP_IMPORT_INVOICES_PKG.g_debug_switch, SQLERRM);
22375 			END IF;
22376 		END IF;
22377 		RETURN FALSE;
22378 
22379 END v_check_invalid_remit_supplier;
22380 
22381 END AP_IMPORT_VALIDATION_PKG;